-- |
-- Module      : Data.Express.Fixtures
-- Copyright   : (c) 2019-2021 Rudy Matela
-- License     : 3-Clause BSD  (see the file LICENSE)
-- Maintainer  : Rudy Matela <rudy@matela.com.br>
--
-- Defines some 'Expr' fixtures to facilitate testing and playing around on
-- the REPL (GHCI).
--
-- * Instead of having to write:
--
--     > > value "&&" (&&) :$ (value "not" not :$ val True) :$ val False
--     > not True && False :: Bool
--
--     Using this module, we can just write:
--
--     > > not' true -&&- false
--     > not True && False :: Bool
--
-- * Instead of having to write:
--
--     > > value "+" ((+)::Int->Int->Int) :$ (value "*" ((*)::Int->Int->Int) :$ var "x" (undefined::Int) :$ var "y" (undefined::Int)) :$ (value "*" ((*)::Int->Int->Int) :$ val (1::Int) :$ val (2::Int))
--     > x * y + 1 * 2 :: Int
--
--     Using this module, we can just write:
--
--     > > xx -*- yy -+- one -*- two
--     > x * y + 1 * 2 :: Int
--
-- * Instead of having to write:
--
--     > > value "||" (||) :$ (value "==" ((==)::Int->Int->Bool) :$ val (3::Int) :$ (value "+" ((+)::Int->Int->Int) :$ var "y" (undefined::Int) :$ val (1::Int))) :$ (value "not" not :$ val False)
--     > 3 == y + 1 || not False :: Bool
--
--     We can just write:
--
--     > > (three -==- yy -+- one) -||- not' false
--     > x == y + 1 || not False :: Bool
--
-- This exports over a hundred symbols
-- to be used mainly when writing unit tests
-- or playing around on GHCi.
--
-- Since the 'Expr' type only allows monomorphic values,
-- encoded polymorphic values are monomorphized
-- usually to the 'Int' type.
--
-- /Beware:/ lifted 'Expr' functions sometimes work for different types.
-- The current version does not have a rationale for types that are included:
-- you have to either try around on the REPL or look at the source to really know.
module Data.Express.Fixtures
  (
  -- * Convenience re-export
    module Data.Express

  -- * Functions and values encoded as Expr or functions of Exprs
  -- | The naming rules are:
  --
  -- * 'Int's are encoded using their English names,
  --   e.g.: 'zero', 'one', 'two';
  --
  -- * 'Char's are encoded using their English names,
  --   e.g.: 'bee', 'cee', 'dee';
  --
  -- * 0-argument constructors are encoded in lowercase,
  --   e.g.: 'false', 'true', 'nothing', 'just';
  --
  -- * lifted constructors are lowercased,
  --   e.g.: 'just';
  --
  -- * lifted functions are primed
  --   e.g.: 'id'', 'negate'', 'head'';
  --
  -- * lifted operators are surrounded by dashes,
  --   e.g.: '-+-', '-*-', '-&&-', '-||-', '-:-'.
  --
  -- * operators are encoded using their English names,
  --   e.g.: 'plus', 'times', 'cons';
  --
  -- * encoded functions are followed by @E@,
  --   e.g.: 'idE', 'notE', 'absE';
  --
  -- * variables have the first character duplicated,
  --   e.g.: 'xx', 'yy', 'xxs';
  --
  -- * encoded values may have the element type appended,
  --   e.g.: 'idInt', 'idBool', 'justInt', 'nilChar'.
  --
  -- Unqualified polymorphic constructors and functions
  -- have their element types bound to 'Int'.
  --
  -- There are exceptions to the above rules such as:
  -- when a name would conflict with a Prelude function.
  -- (e.g.: 'orE' and 'andE')

  -- ** Booleans
  , b_, pp, qq, rr, pp'
  , false
  , true
  , notE
  , orE
  , andE
  , implies
  , not'
  , (-||-)
  , (-&&-)
  , (-==>-)
  , (-==-)
  , (-/=-)
  , (-<=-)
  , (-<-)
  , compare'
  , if'

  -- ** Integers
  , i_, xx, yy, zz, xx'
  , ii, jj, kk, ii'
  , ll, mm, nn
  , zero, one, two, three, four, five, six
  , seven, eight, nine, ten, eleven, twelve
  , minusOne, minusTwo
  , idE, negateE, absE, signumE
  , idInt
  , idBool
  , idChar
  , idInts
  , idBools
  , idString
  , id', const', negate', abs', signum'
  , plus, times, minus
  , (-+-), (-*-)
  , ff, ffE
  , gg, ggE
  , hh, hhE
  , (-?-)
  , (-$-)
  , odd'
  , even'

  -- ** Chars
  , c_, cs_
  , cc, dd, ccs
  , ae, bee, cee, dee, zed, zee
  , space, lineBreak
  , ord'
  , ordE

  -- ** Lists
  , is_
  , xxs
  , yys
  , zzs
  , nil
  , emptyString
  , nilInt
  , nilBool
  , nilChar
  , cons
  , consInt
  , consBool
  , consChar
  , (-:-)
  , unit
  , (-++-)
  , head'
  , tail'
  , null'
  , length'
  , elem'
  , sort'
  , insert'
  , bs_, pps, qqs
  , and', or'
  , sum', product'
  , appendInt

  -- ** Maybes
  , nothing
  , nothingInt
  , nothingBool
  , just
  , justInt
  , justBool

  -- ** Tuples
  , comma
  , pair
  , (-|-)
  , triple
  , quadruple
  , quintuple
  , sixtuple

  -- ** Higher order
  , compose
  , mapE
  , (-.-)
  , map'

  -- ** Enum
  , enumFrom',   (-..)
  , enumFromTo', (-..-)
  , enumFromThen', (-...)
  , enumFromThenTo', (-...-)
  )
where

import Data.Express
import Data.Maybe
import Data.Typeable (Typeable, typeOf)
import Data.Char
import Data.List

int :: Int
int :: Int
int  =  Int
forall a. HasCallStack => a
undefined

bool :: Bool
bool :: Bool
bool  =  Bool
forall a. HasCallStack => a
undefined

char :: Char
char :: Char
char  =  Char
forall a. HasCallStack => a
undefined

string :: String
string :: String
string  =  String
forall a. HasCallStack => a
undefined

-- | 'Expr' representing a hole of 'Bool' type.
--
-- > > b_
-- > _ :: Bool
b_ :: Expr
b_ :: Expr
b_  =  Bool -> Expr
forall a. Typeable a => a -> Expr
hole Bool
bool

-- | 'Expr' representing a variable @p :: `Bool`@.
--
-- > > pp
-- > p :: Bool
pp :: Expr
pp :: Expr
pp  =  String -> Bool -> Expr
forall a. Typeable a => String -> a -> Expr
var String
"p" Bool
bool

-- | 'Expr' representing a variable @q :: `Bool`@.
--
-- > > qq
-- > q :: Bool
qq :: Expr
qq :: Expr
qq  =  String -> Bool -> Expr
forall a. Typeable a => String -> a -> Expr
var String
"q" Bool
bool

-- | 'Expr' representing a variable @r :: `Bool`@.
--
-- > > rr
-- > r :: Bool
rr :: Expr
rr :: Expr
rr  =  String -> Bool -> Expr
forall a. Typeable a => String -> a -> Expr
var String
"r" Bool
bool

-- | 'Expr' representing a variable @p' :: `Bool`@.
--
-- > > pp'
-- > p' :: Bool
pp' :: Expr
pp' :: Expr
pp'  =  String -> Bool -> Expr
forall a. Typeable a => String -> a -> Expr
var String
"p'" Bool
bool


-- | 'False' encoded as an 'Expr'.
--
-- > > false
-- > False :: Bool
false :: Expr
false :: Expr
false  =  Bool -> Expr
forall a. (Typeable a, Show a) => a -> Expr
val Bool
False

-- | 'True' encoded as an 'Expr'.
--
-- > > true
-- > True :: Bool
true :: Expr
true :: Expr
true  =  Bool -> Expr
forall a. (Typeable a, Show a) => a -> Expr
val Bool
True

-- | The function 'not' encoded as an 'Expr'.
--
-- > > notE
-- > not :: Bool -> Bool
notE :: Expr
notE :: Expr
notE  =  String -> (Bool -> Bool) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"not" Bool -> Bool
not

-- | The function 'and' encoded as an 'Expr'.
--
-- > > andE
-- > (&&) :: Bool -> Bool -> Bool
andE :: Expr
andE :: Expr
andE  =  String -> (Bool -> Bool -> Bool) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"&&" Bool -> Bool -> Bool
(&&)

-- | The function 'or' encoded as an 'Expr'.
--
-- > > orE
-- > (||) :: Bool -> Bool -> Bool
orE :: Expr
orE :: Expr
orE  =  String -> (Bool -> Bool -> Bool) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"||" Bool -> Bool -> Bool
(||)

-- | The function @==>@ lifted over 'Expr's.
--
-- > > false -==>- true
-- > False ==> True :: Bool
--
-- > > evl $ false -==>- true :: Bool
-- > True
(-==>-) :: Expr -> Expr -> Expr
Expr
e1 -==>- :: Expr -> Expr -> Expr
-==>- Expr
e2  =  Expr
implies Expr -> Expr -> Expr
:$ Expr
e1 Expr -> Expr -> Expr
:$ Expr
e2
infixr 0 -==>-

-- | The @==>@ operator encoded as an 'Expr'
implies :: Expr
implies :: Expr
implies  =  String -> (Bool -> Bool -> Bool) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"==>" Bool -> Bool -> Bool
(==>)
  where
  Bool
False ==> :: Bool -> Bool -> Bool
==> Bool
_  =  Bool
True
  Bool
True  ==> Bool
p  =  Bool
p

-- | The function 'not' lifted over the 'Expr' type.
--
-- > > not' false
-- > not False :: Bool
--
-- > > evalBool $ not' false
-- > True
--
-- > > not' pp
-- > not p :: Bool
not' :: Expr -> Expr
not' :: Expr -> Expr
not' Expr
pp  =  Expr
notE Expr -> Expr -> Expr
:$ Expr
pp

-- | The function '&&' lifted over the 'Expr' type.
--
-- > > pp -&&- qq
-- > p && q :: Bool
--
-- > > false -&&- true
-- > False && True :: Bool
--
-- > > evalBool $ false -&&- true
-- > False
(-&&-) :: Expr -> Expr -> Expr
Expr
pp -&&- :: Expr -> Expr -> Expr
-&&- Expr
qq  =  Expr
andE Expr -> Expr -> Expr
:$ Expr
pp Expr -> Expr -> Expr
:$ Expr
qq
infixr 3 -&&-

-- | The function '||' lifted over the 'Expr' type.
--
-- > > pp -||- qq
-- > p || q :: Bool
--
-- > > false -||- true
-- > False || True :: Bool
--
-- > > evalBool $ false -||- true
-- > True
(-||-) :: Expr -> Expr -> Expr
Expr
pp -||- :: Expr -> Expr -> Expr
-||- Expr
qq  =  Expr
orE Expr -> Expr -> Expr
:$ Expr
pp Expr -> Expr -> Expr
:$ Expr
qq
infixr 2 -||-

-- | A typed hole of 'Int' type.
--
-- > > i_
-- > _ :: Int
i_ :: Expr
i_ :: Expr
i_  =  Int -> Expr
forall a. Typeable a => a -> Expr
hole Int
int

-- | A variable @x@ of 'Int' type.
--
-- > > xx
-- > x :: Int
xx :: Expr
xx :: Expr
xx  =  String -> Int -> Expr
forall a. Typeable a => String -> a -> Expr
var String
"x" Int
int

-- | A variable @y@ of 'Int' type.
--
-- > > yy
-- > y :: Int
yy :: Expr
yy :: Expr
yy  =  String -> Int -> Expr
forall a. Typeable a => String -> a -> Expr
var String
"y" Int
int

-- | A variable @z@ of 'Int' type.
--
-- > > zz
-- > z :: Int
zz :: Expr
zz :: Expr
zz  =  String -> Int -> Expr
forall a. Typeable a => String -> a -> Expr
var String
"z" Int
int

-- | A variable @x'@ of 'Int' type.
--
-- > > xx'
-- > x' :: Int
xx' :: Expr
xx' :: Expr
xx'  =  String -> Int -> Expr
forall a. Typeable a => String -> a -> Expr
var String
"x'" Int
int


-- | A variable @i@ of 'Int' type.
--
-- > > ii
-- > i :: Int
ii :: Expr
ii :: Expr
ii  =  String -> Int -> Expr
forall a. Typeable a => String -> a -> Expr
var String
"i" Int
int

-- | A variable @j@ of 'Int' type.
--
-- > > jj
-- > j :: Int
jj :: Expr
jj :: Expr
jj  =  String -> Int -> Expr
forall a. Typeable a => String -> a -> Expr
var String
"j" Int
int

-- | A variable @k@ of 'Int' type.
--
-- > > kk
-- > k :: Int
kk :: Expr
kk :: Expr
kk  =  String -> Int -> Expr
forall a. Typeable a => String -> a -> Expr
var String
"k" Int
int

-- | A variable @i'@ of 'Int' type.
--
-- > > ii'
-- > i' :: Int
ii' :: Expr
ii' :: Expr
ii'  =  String -> Int -> Expr
forall a. Typeable a => String -> a -> Expr
var String
"i'" Int
int

-- | A variable @l@ of 'Int' type.
--
-- > > ll
-- > l :: Int
ll :: Expr
ll :: Expr
ll  =  String -> Int -> Expr
forall a. Typeable a => String -> a -> Expr
var String
"l" Int
int

-- | A variable @m@ of 'Int' type.
--
-- > > mm
-- > m :: Int
mm :: Expr
mm :: Expr
mm  =  String -> Int -> Expr
forall a. Typeable a => String -> a -> Expr
var String
"m" Int
int

-- | A variable @n@ of 'Int' type.
--
-- > > nn
-- > n :: Int
nn :: Expr
nn :: Expr
nn  =  String -> Int -> Expr
forall a. Typeable a => String -> a -> Expr
var String
"n" Int
int

-- | The value @0@ bound to the 'Int' type encoded as an 'Expr'.
--
-- > > zero
-- > 0 :: Int
zero :: Expr
zero :: Expr
zero  =  Int -> Expr
forall a. (Typeable a, Show a) => a -> Expr
val (Int
0 :: Int)

-- | The value @1@ bound to the 'Int' type encoded as an 'Expr'.
--
-- > > one
-- > 1 :: Int
one :: Expr
one :: Expr
one  =  Int -> Expr
forall a. (Typeable a, Show a) => a -> Expr
val (Int
1 :: Int)

-- | The value @2@ bound to the 'Int' type encoded as an 'Expr'.
--
-- > > two
-- > 2 :: Int
two :: Expr
two :: Expr
two  =  Int -> Expr
forall a. (Typeable a, Show a) => a -> Expr
val (Int
2 :: Int)

-- | The value @3@ bound to the 'Int' type encoded as an 'Expr'.
--
-- > > three
-- > 3 :: Int
three :: Expr
three :: Expr
three  =  Int -> Expr
forall a. (Typeable a, Show a) => a -> Expr
val (Int
3 :: Int)

-- | The value @4@ bound to the 'Int' type encoded as an 'Expr'.
--
-- > > four
-- > 4 :: Int
four :: Expr
four :: Expr
four  =  Int -> Expr
forall a. (Typeable a, Show a) => a -> Expr
val (Int
4 :: Int)

-- | The value @5@ bound to the 'Int' type encoded as an 'Expr'.
--
-- > > five
-- > 5 :: Int
five :: Expr
five :: Expr
five  =  Int -> Expr
forall a. (Typeable a, Show a) => a -> Expr
val (Int
5 :: Int)

-- | The value @6@ bound to the 'Int' type encoded as an 'Expr'.
--
-- > > six
-- > 6 :: Int
six :: Expr
six :: Expr
six  =  Int -> Expr
forall a. (Typeable a, Show a) => a -> Expr
val (Int
6 :: Int)

-- | The value @7@ bound to the 'Int' type encoded as an 'Expr'.
--
-- > > seven
-- > 7 :: Int
seven :: Expr
seven :: Expr
seven  =  Int -> Expr
forall a. (Typeable a, Show a) => a -> Expr
val (Int
7 :: Int)

-- | The value @8@ bound to the 'Int' type encoded as an 'Expr'.
--
-- > > eight
-- > 8 :: Int
eight :: Expr
eight :: Expr
eight  =  Int -> Expr
forall a. (Typeable a, Show a) => a -> Expr
val (Int
8 :: Int)

-- | The value @9@ bound to the 'Int' type encoded as an 'Expr'.
--
-- > > nine
-- > 9 :: Int
nine :: Expr
nine :: Expr
nine  =  Int -> Expr
forall a. (Typeable a, Show a) => a -> Expr
val (Int
9 :: Int)

-- | The value @10@ bound to the 'Int' type encoded as an 'Expr'.
--
-- > > ten
-- > 10 :: Int
ten :: Expr
ten :: Expr
ten  =  Int -> Expr
forall a. (Typeable a, Show a) => a -> Expr
val (Int
10 :: Int)

-- | The value @11@ bound to the 'Int' type encoded as an 'Expr'.
--
-- > > eleven
-- > 11 :: Int
eleven :: Expr
eleven :: Expr
eleven  =  Int -> Expr
forall a. (Typeable a, Show a) => a -> Expr
val (Int
11 :: Int)

-- | The value @12@ bound to the 'Int' type encoded as an 'Expr'.
--
-- > > twelve
-- > 12 :: Int
twelve :: Expr
twelve :: Expr
twelve  =  Int -> Expr
forall a. (Typeable a, Show a) => a -> Expr
val (Int
12 :: Int)

-- | The value @-1@ bound to the 'Int' type encoded as an 'Expr'.
--
-- > > minusOne
-- > -1 :: Int
minusOne :: Expr
minusOne :: Expr
minusOne  =  Int -> Expr
forall a. (Typeable a, Show a) => a -> Expr
val (-Int
1 :: Int)

-- | The value @-2@ bound to the 'Int' type encoded as an 'Expr'.
--
-- > > minusOne
-- > -2 :: Int
minusTwo :: Expr
minusTwo :: Expr
minusTwo  =  Int -> Expr
forall a. (Typeable a, Show a) => a -> Expr
val (-Int
2 :: Int)

-- | A variable function @f@ of 'Int -> Int' type lifted over the 'Expr' type.
--
-- > > ff xx
-- > f x :: Int
--
-- > > ff one
-- > f 1 :: Int
ff :: Expr -> Expr
ff :: Expr -> Expr
ff = (Expr
ffE Expr -> Expr -> Expr
:$)

-- | A variable @f@ of 'Int -> Int' type encoded as an 'Expr'.
--
-- > > ffE
-- > f :: Int -> Int
ffE :: Expr
ffE :: Expr
ffE = String -> (Int -> Int) -> Expr
forall a. Typeable a => String -> a -> Expr
var String
"f" (Int -> Int
forall a. HasCallStack => a
undefined :: Int -> Int)

-- | A variable function @g@ of 'Int -> Int' type lifted over the 'Expr' type.
--
-- > > gg yy
-- > g y :: Int
--
-- > > gg minusTwo
-- > gg (-2) :: Int
gg :: Expr -> Expr
gg :: Expr -> Expr
gg = (Expr
ggE Expr -> Expr -> Expr
:$)

-- | A variable @g@ of 'Int -> Int' type encoded as an 'Expr'.
--
-- > > ggE
-- > g :: Int -> Int
ggE :: Expr
ggE :: Expr
ggE = String -> (Int -> Int) -> Expr
forall a. Typeable a => String -> a -> Expr
var String
"g" (Int -> Int
forall a. HasCallStack => a
undefined :: Int -> Int)

-- | A variable function @h@ of 'Int -> Int' type lifted over the 'Expr' type.
--
-- > > hh zz
-- > h z :: Int
hh :: Expr -> Expr
hh :: Expr -> Expr
hh = (Expr
hhE Expr -> Expr -> Expr
:$)

-- | A variable @h@ of 'Int -> Int' type encoded as an 'Expr'.
--
-- > > hhE
-- > h :: Int -> Int
hhE :: Expr
hhE :: Expr
hhE = String -> (Int -> Int) -> Expr
forall a. Typeable a => String -> a -> Expr
var String
"h" (Int -> Int
forall a. HasCallStack => a
undefined :: Int -> Int)

-- | A variable binary operator @?@ lifted over the 'Expr' type.
--   Works for 'Int', 'Bool', 'Char', @[Int]@ and 'String'.
--
-- > > xx -?- yy
-- > x ? y :: Int
--
-- > > pp -?- qq
-- > p ? q :: Bool
--
-- > > xx -?- qq
-- > *** Exception: (-?-): cannot apply `(?) :: * -> * -> *` to `x :: Int' and `q :: Bool'.  Unhandled types?
(-?-) :: Expr -> Expr -> Expr
Expr
ex -?- :: Expr -> Expr -> Expr
-?- Expr
ey  =  Expr -> Maybe Expr -> Expr
forall a. a -> Maybe a -> a
fromMaybe Expr
forall a. a
err (Maybe Expr -> Expr) -> Maybe Expr -> Expr
forall a b. (a -> b) -> a -> b
$ (Expr -> Expr -> Maybe Expr
$$ Expr
ey) (Expr -> Maybe Expr) -> Expr -> Maybe Expr
forall a b. (a -> b) -> a -> b
$ Expr -> [Expr] -> Expr
forall a. a -> [a] -> a
headOr Expr
forall a. a
err ([Expr] -> Expr) -> [Expr] -> Expr
forall a b. (a -> b) -> a -> b
$ (Expr -> Maybe Expr) -> [Expr] -> [Expr]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Expr -> Expr -> Maybe Expr
$$ Expr
ex)
  [ String -> (Int -> Int -> Int) -> Expr
forall a. Typeable a => String -> a -> Expr
var String
"?" (Int -> Int -> Int
forall a. HasCallStack => a
undefined :: Int -> Int -> Int)
  , String -> (Bool -> Bool -> Bool) -> Expr
forall a. Typeable a => String -> a -> Expr
var String
"?" (Bool -> Bool -> Bool
forall a. HasCallStack => a
undefined :: Bool -> Bool -> Bool)
  , String -> (Char -> Char -> Char) -> Expr
forall a. Typeable a => String -> a -> Expr
var String
"?" (Char -> Char -> Char
forall a. HasCallStack => a
undefined :: Char -> Char -> Char)
  , String -> ([Int] -> [Int] -> [Int]) -> Expr
forall a. Typeable a => String -> a -> Expr
var String
"?" ([Int] -> [Int] -> [Int]
forall a. HasCallStack => a
undefined :: [Int] -> [Int] -> [Int])
  , String -> (String -> String -> String) -> Expr
forall a. Typeable a => String -> a -> Expr
var String
"?" (String -> String -> String
forall a. HasCallStack => a
undefined :: String -> String -> String)
  ]
  where
  err :: a
err  =  String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"(-?-): cannot apply `(?) :: * -> * -> *` to `"
               String -> String -> String
forall a. [a] -> [a] -> [a]
++ Expr -> String
forall a. Show a => a -> String
show Expr
ex String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"' and `" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Expr -> String
forall a. Show a => a -> String
show Expr
ey String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"'.  Unhandled types?"

-- | The operator '+' for the 'Int' type for use on 'Expr's.  (See also 'plus'.)
--
-- > > two -+- three
-- > 2 + 3 :: Int
--
-- > > minusOne -+- minusTwo -+- zero
-- > ((-1) + (-2)) + 0 :: Int
--
-- > > xx -+- (yy -+- zz)
-- > x + (y + z) :: Int
(-+-) :: Expr -> Expr -> Expr
Expr
e1 -+- :: Expr -> Expr -> Expr
-+- Expr
e2 = Expr
plus Expr -> Expr -> Expr
:$ Expr
e1 Expr -> Expr -> Expr
:$ Expr
e2
infixl 6 -+-

-- | The operator '+' for the 'Int' type.  (See also '-+-'.)
--
-- > > plus
-- > (+) :: Int -> Int -> Int
--
-- > > plus :$ one
-- > (1 +) :: Int -> Int
--
-- > > plus :$ xx :$ yy
-- > x + y :: Int
plus :: Expr
plus :: Expr
plus = String -> (Int -> Int -> Int) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"+" (Int -> Int -> Int
forall a. Num a => a -> a -> a
(+) :: Int -> Int -> Int)

-- | The operator '*' for the 'Int' type lifted over the 'Expr' type.  (See also 'times'.)
--
-- > > three -*- three
-- > 9 :: Int
--
-- > > one -*- two -*- three
-- > (1 * 2) * 3 :: Int
--
-- > > two -*- xx
-- > 2 * x :: Int
(-*-) :: Expr -> Expr -> Expr
Expr
e1 -*- :: Expr -> Expr -> Expr
-*- Expr
e2 = Expr
times Expr -> Expr -> Expr
:$ Expr
e1 Expr -> Expr -> Expr
:$ Expr
e2
infixl 7 -*-

-- | The operator '*' for the 'Int' type.  (See also '-*-'.)
--
-- > > times
-- > (*) :: Int -> Int -> Int
--
-- > > times :$ two
-- > (2 *) :: Int -> Int
--
-- > > times :$ xx :$ yy
-- > x * y :: Int
times :: Expr
times :: Expr
times  =  String -> (Int -> Int -> Int) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"*" (Int -> Int -> Int
forall a. Num a => a -> a -> a
(*) :: Int -> Int -> Int)

-- | The subtraction '-' operator encoded as an 'Expr'.
--
-- > > minus :$ one
-- > (1 -) :: Int -> Int
--
-- > > minus :$ one :$ zero
-- > 1 - 0 :: Int
minus :: Expr
minus :: Expr
minus  =  String -> (Int -> Int -> Int) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"-" ((-) :: Int -> Int -> Int)

-- | Constructs an application of 'id' as an 'Expr'.
--   Only works for 'Int', 'Bool', 'Char', 'String', @[Int]@, @[Bool]@.
--
-- > > id' yy
-- > id yy :: Int
--
-- > > id' one
-- > id 1 :: Int
--
-- > > evl (id' one) :: Int
-- > 1
--
-- > > id' pp
-- > id p :: Bool
--
-- > > id' false
-- > id' False :: Bool
--
-- > > evl (id' true) :: Bool
-- > True :: Bool
id' :: Expr -> Expr
id' :: Expr -> Expr
id' Expr
e  =  Expr -> [Expr] -> Expr
forall a. a -> [a] -> a
headOr Expr
forall a. a
err ([Expr] -> Expr) -> [Expr] -> Expr
forall a b. (a -> b) -> a -> b
$ (Expr -> Maybe Expr) -> [Expr] -> [Expr]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Expr -> Expr -> Maybe Expr
$$ Expr
e)
  [ Expr
idInt
  , Expr
idBool
  , Expr
idChar
  , Expr
idInts
  , Expr
idBools
  , Expr
idString
  ]
  where
  err :: a
err  =  String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"id': unhandled type " String -> String -> String
forall a. [a] -> [a] -> [a]
++ TypeRep -> String
forall a. Show a => a -> String
show (Expr -> TypeRep
typ Expr
e)

-- | The function 'id' for the 'Int' type encoded as an 'Expr'.  (See also 'id''.)
--
-- > > idE :$ xx
-- > id x :: Int
--
-- > > idE :$ zero
-- > id 0 :: Int
--
-- > > evaluate $ idE :$ zero :: Maybe Int
-- > Just 0
idE :: Expr
idE :: Expr
idE  =  Expr
idInt

-- | The function 'id' encoded as an 'Expr'.  (cf. 'id'')
idInt,idBool,idChar,idInts,idBools,idString :: Expr
idInt :: Expr
idInt     =  String -> (Int -> Int) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"id" (Int -> Int
forall a. a -> a
id :: Id Int)
idBool :: Expr
idBool    =  String -> (Bool -> Bool) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"id" (Bool -> Bool
forall a. a -> a
id :: Id Bool)
idChar :: Expr
idChar    =  String -> (Char -> Char) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"id" (Char -> Char
forall a. a -> a
id :: Id Char)
idInts :: Expr
idInts    =  String -> ([Int] -> [Int]) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"id" ([Int] -> [Int]
forall a. a -> a
id :: Id [Int])
idBools :: Expr
idBools   =  String -> Id [Bool] -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"id" (Id [Bool]
forall a. a -> a
id :: Id [Bool])
idString :: Expr
idString  =  String -> (String -> String) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"id" (String -> String
forall a. a -> a
id :: Id String)
type Id a = a -> a

-- | The 'const' function lifted over the 'Expr' type.
--
-- > > const' zero one
-- > const 0 1 :: Int
--
-- This works for the argument types 'Int', 'Char', 'Bool' and their lists.
const' :: Expr -> Expr -> Expr
const' :: Expr -> Expr -> Expr
const' Expr
e1 Expr
e2  =  (Expr -> Expr -> Expr
:$ Expr
e2) (Expr -> Expr) -> ([Expr] -> Expr) -> [Expr] -> Expr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expr -> [Expr] -> Expr
forall a. a -> [a] -> a
headOr Expr
forall a. a
err ([Expr] -> Expr) -> [Expr] -> Expr
forall a b. (a -> b) -> a -> b
$ (Expr -> Maybe Expr) -> [Expr] -> [Expr]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Expr -> Expr -> Maybe Expr
$$ Expr
e1)
  [ String -> (Int -> Int -> Int) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"const" (Int -> Int -> Int
forall a b. a -> b -> a
const :: Int -> Int -> Int)
  , String -> (Bool -> Bool -> Bool) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"const" (Bool -> Bool -> Bool
forall a b. a -> b -> a
const :: Bool -> Bool -> Bool)
  , String -> (Char -> Char -> Char) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"const" (Char -> Char -> Char
forall a b. a -> b -> a
const :: Char -> Char -> Char)
  , String -> ([Int] -> [Int] -> [Int]) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"const" ([Int] -> [Int] -> [Int]
forall a b. a -> b -> a
const :: [Int] -> [Int] -> [Int])
  , String -> ([Bool] -> Id [Bool]) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"const" ([Bool] -> Id [Bool]
forall a b. a -> b -> a
const :: [Bool] -> [Bool] -> [Bool])
  , String -> (String -> String -> String) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"const" (String -> String -> String
forall a b. a -> b -> a
const :: String -> String -> String)
  ]
  where
  err :: a
err  =  String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"const': unhandled type " String -> String -> String
forall a. [a] -> [a] -> [a]
++ TypeRep -> String
forall a. Show a => a -> String
show (Expr -> TypeRep
typ Expr
e1)

-- | 'negate' over the 'Int' type lifted over the 'Expr' type.
--
-- > > negate' xx
-- > negate x :: Int
--
-- > > evl (negate' one) :: Int
-- > -1
negate' :: Expr -> Expr
negate' :: Expr -> Expr
negate' Expr
e  =  Expr
negateE Expr -> Expr -> Expr
:$ Expr
e

-- | 'negate' over the 'Int' type encoded as an 'Expr'
--
-- > > negateE
-- > negate :: Int -> Int
negateE :: Expr
negateE :: Expr
negateE  =  String -> (Int -> Int) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"negate" (Int -> Int
forall a. Num a => a -> a
negate :: Int -> Int)

-- | 'abs' over the 'Int' type lifted over the 'Expr' type.
--
-- > > abs' xx'
-- > abs x' :: Int
--
-- > > evl (abs' minusTwo) :: Int
-- > 2
abs' :: Expr -> Expr
abs' :: Expr -> Expr
abs' Expr
e  =  Expr
absE Expr -> Expr -> Expr
:$ Expr
e

-- | 'abs' over the 'Int' type encoded as an 'Expr'.
--
-- > > absE
-- > abs :: Int -> Int
absE :: Expr
absE :: Expr
absE  =  String -> (Int -> Int) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"abs" (Int -> Int
forall a. Num a => a -> a
abs :: Int -> Int)

-- | 'signum' over the 'Int' type lifted over the 'Expr' type.
--
-- > > signum' xx'
-- > signum x' :: Int
--
-- > > evl (signum' minusTwo) :: Int
-- > -1
signum' :: Expr -> Expr
signum' :: Expr -> Expr
signum' Expr
e  =  Expr
signumE Expr -> Expr -> Expr
:$ Expr
e

-- | 'signum' over the 'Int' type encoded as an 'Expr'.
--
-- > > signumE
-- > signum :: Int -> Int
signumE :: Expr
signumE :: Expr
signumE  =  String -> (Int -> Int) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"signum" (Int -> Int
forall a. Num a => a -> a
signum :: Int -> Int)

-- | 'odd' with an 'Int' argument lifted over the 'Expr' type.
--
-- > > odd' (xx -+- one)
-- > odd (x + 1) :: Bool
--
-- > > evl (odd' two) :: Bool
-- > False
odd' :: Expr -> Expr
odd' :: Expr -> Expr
odd' = (Expr
oddE Expr -> Expr -> Expr
:$) where oddE :: Expr
oddE = String -> (Int -> Bool) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"odd" (Int -> Bool
forall a. Integral a => a -> Bool
odd :: Int -> Bool)

-- | 'even' with an 'Int' argument lifted over the 'Expr' type.
--
-- > > even' (xx -+- two)
-- > even (x + 2) :: Bool
--
-- > > evl (even' two) :: Bool
-- > True
even' :: Expr -> Expr
even' :: Expr -> Expr
even' = (Expr
evenE Expr -> Expr -> Expr
:$) where evenE :: Expr
evenE = String -> (Int -> Bool) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"even" (Int -> Bool
forall a. Integral a => a -> Bool
even :: Int -> Bool)

-- | A hole of 'Char' type encoded as an 'Expr'.
--
-- > > c_
-- > _ :: Char
c_ :: Expr
c_ :: Expr
c_  =  Char -> Expr
forall a. Typeable a => a -> Expr
hole Char
char

-- | A hole of 'String' type encoded as an 'Expr'.
--
-- > > cs_
-- > _ :: [Char]
cs_ :: Expr
cs_ :: Expr
cs_  =  String -> Expr
forall a. Typeable a => a -> Expr
hole [Char
char]

-- | A variable named @c@ of type 'Char' encoded as an 'Expr'.
--
-- > > cc
-- > c :: Char
cc :: Expr
cc :: Expr
cc  =  String -> Char -> Expr
forall a. Typeable a => String -> a -> Expr
var String
"c" Char
char

-- | A variable named @c@ of type 'Char' encoded as an 'Expr'.
--
-- > > dd
-- > d :: Char
dd :: Expr
dd :: Expr
dd  =  String -> Char -> Expr
forall a. Typeable a => String -> a -> Expr
var String
"d" Char
char

-- | A variable named @cs@ of type 'String' encoded as an 'Expr'.
--
-- > > ccs
-- > cs :: [Char]
ccs :: Expr
ccs :: Expr
ccs  =  String -> String -> Expr
forall a. Typeable a => String -> a -> Expr
var String
"cs" [Char
char]

-- | The character @\'a\'@ encoded as an 'Expr'.
--
-- > > ae
-- > 'a' :: Char
--
-- > > evl ae :: Char
-- > 'a'
ae :: Expr
ae :: Expr
ae  =  Char -> Expr
forall a. (Typeable a, Show a) => a -> Expr
val Char
'a'
-- The English name for letter 'a' is not really 'ae', but simply 'a'.

-- | The character @\'b\'@ encoded as an 'Expr'
--
-- > > bee
-- > 'b' :: Char
--
-- > > evl bee :: Char
-- > 'b'
bee :: Expr
bee :: Expr
bee  =  Char -> Expr
forall a. (Typeable a, Show a) => a -> Expr
val Char
'b'

-- | The character @\'c\'@ encoded as an 'Expr'
--
-- > > cee
-- > 'c' :: Char
--
-- > > evl cee :: Char
-- > 'c'
cee :: Expr
cee :: Expr
cee  =  Char -> Expr
forall a. (Typeable a, Show a) => a -> Expr
val Char
'c'

-- | The character @\'d\'@ encoded as an 'Expr'
--
-- > > dee
-- > 'd' :: Char
--
-- > > evl dee :: Char
-- > 'd'
dee :: Expr
dee :: Expr
dee  =  Char -> Expr
forall a. (Typeable a, Show a) => a -> Expr
val Char
'd'

-- | The character @\'z\'@ encoded as an 'Expr'
--
-- > > zed
-- > 'z' :: Char
--
-- > > evl zed :: Char
-- > 'z'
--
-- (cf. 'zee')
zed :: Expr
zed :: Expr
zed  =  Char -> Expr
forall a. (Typeable a, Show a) => a -> Expr
val Char
'z'

-- | The character @\'z\'@ encoded as an 'Expr'
--
-- > > zee
-- > 'z' :: Char
--
-- > > evl zee :: Char
-- > 'z'
--
-- (cf. 'zed')
zee :: Expr
zee :: Expr
zee  =  Char -> Expr
forall a. (Typeable a, Show a) => a -> Expr
val Char
'z'

-- | The space character encoded as an 'Expr'
--
-- > > space
-- > ' ' :: Char
space :: Expr
space :: Expr
space = Char -> Expr
forall a. (Typeable a, Show a) => a -> Expr
val Char
' '

-- | The line break character encoded as an 'Expr'
--
-- > > lineBreak
-- > '\n' :: Char
lineBreak :: Expr
lineBreak :: Expr
lineBreak = Char -> Expr
forall a. (Typeable a, Show a) => a -> Expr
val Char
'\n'

-- | The 'ord' function lifted over 'Expr'
--
-- > > ord' bee
-- > ord 'b' :: Int
--
-- > > evl (ord' bee)
-- > 98
ord' :: Expr -> Expr
ord' :: Expr -> Expr
ord' = (Expr
ordE Expr -> Expr -> Expr
:$)

-- | The 'ord' function encoded as an 'Expr'
ordE :: Expr
ordE :: Expr
ordE = String -> (Char -> Int) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"ord" Char -> Int
ord

-- | A typed hole of @[Int]@ type encoded as an 'Expr'.
--
-- > > is_
-- > _ :: [Int]
is_ :: Expr
is_ :: Expr
is_  =  [Int] -> Expr
forall a. Typeable a => a -> Expr
hole [Int
int]

-- | A variable named @xs@ of type @[Int]@ encoded as an 'Expr'.
--
-- > > xxs
-- > xs :: [Int]
xxs :: Expr
xxs :: Expr
xxs  =  String -> [Int] -> Expr
forall a. Typeable a => String -> a -> Expr
var String
"xs" [Int
int]

-- | A variable named @ys@ of type @[Int]@ encoded as an 'Expr'.
--
-- > > yys
-- > ys :: [Int]
yys :: Expr
yys :: Expr
yys  =  String -> [Int] -> Expr
forall a. Typeable a => String -> a -> Expr
var String
"ys" [Int
int]

-- | A variable named @zs@ of type @[Int]@ encoded as an 'Expr'.
--
-- > > yys
-- > ys :: [Int]
zzs :: Expr
zzs :: Expr
zzs  =  String -> [Int] -> Expr
forall a. Typeable a => String -> a -> Expr
var String
"zs" [Int
int]

-- | An empty list of type @[Int]@ encoded as an 'Expr'.
--
-- > > nil
-- > [] :: [Int]
nil :: Expr
nil :: Expr
nil  =  Expr
nilInt

-- | An empty 'String' encoded as an 'Expr'.
--
-- > > emptyString
-- > "" :: String
emptyString :: Expr
emptyString :: Expr
emptyString  =  String -> Expr
forall a. (Typeable a, Show a) => a -> Expr
val String
""

-- | The empty list '[]' encoded as an 'Expr'.
nilInt, nilBool, nilChar :: Expr
nilInt :: Expr
nilInt   =  [Int] -> Expr
forall a. (Typeable a, Show a) => a -> Expr
val ([] :: [Int])
nilBool :: Expr
nilBool  =  [Bool] -> Expr
forall a. (Typeable a, Show a) => a -> Expr
val ([] :: [Bool])
nilChar :: Expr
nilChar  =  String -> String -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"[]" ([] :: [Char])

-- | The list constructor with 'Int' as element type encoded as an 'Expr'.
--
-- > > cons
-- > (:) :: Int -> [Int] -> [Int]
--
-- > > cons :$ one :$ nil
-- > [1] :: [Int]
--
-- Consider using '-:-' and 'unit' when building lists of 'Expr'.
cons :: Expr
cons :: Expr
cons  =  Expr
consInt

-- | The list constructor @ : @ encoded as an 'Expr'.
consInt, consBool, consChar :: Expr
consInt :: Expr
consInt   =  String -> Cons Int -> Expr
forall a. Typeable a => String -> a -> Expr
value String
":" ((:) :: Cons Int)
consBool :: Expr
consBool  =  String -> Cons Bool -> Expr
forall a. Typeable a => String -> a -> Expr
value String
":" ((:) :: Cons Bool)
consChar :: Expr
consChar  =  String -> Cons Char -> Expr
forall a. Typeable a => String -> a -> Expr
value String
":" ((:) :: Cons Char)
type Cons a = a -> [a] -> [a]

-- | 'unit' constructs a list with a single element.
--   This works for elements of type 'Int', 'Char' and 'Bool'.
--
-- > > unit one
-- > [1]
--
-- > > unit false
-- > [False]
unit :: Expr -> Expr
unit :: Expr -> Expr
unit Expr
e  =  Expr
e Expr -> Expr -> Expr
-:- Expr
nil'
  where
  nil' :: Expr
nil' | Expr -> TypeRep
typ Expr
e TypeRep -> TypeRep -> Bool
forall a. Eq a => a -> a -> Bool
== Expr -> TypeRep
typ Expr
i_  =  Expr
nil
       | Expr -> TypeRep
typ Expr
e TypeRep -> TypeRep -> Bool
forall a. Eq a => a -> a -> Bool
== Expr -> TypeRep
typ Expr
c_  =  Expr
emptyString
       | Expr -> TypeRep
typ Expr
e TypeRep -> TypeRep -> Bool
forall a. Eq a => a -> a -> Bool
== Expr -> TypeRep
typ Expr
b_  =  Expr
nilBool

-- | The list constructor lifted over the 'Expr' type.
--   Works for the element types 'Int', 'Char' and 'Bool'.
--
-- > > zero -:- one -:- unit two
-- > [0,1,2] :: [Int]
--
-- > > zero -:- one -:- two -:- nil
-- > [0,1,2] :: [Int]
--
-- > > bee -:- unit cee
-- > "bc" :: [Char]
(-:-) :: Expr -> Expr -> Expr
Expr
e1 -:- :: Expr -> Expr -> Expr
-:- Expr
e2  =  (Expr -> Expr -> Expr
:$ Expr
e2) (Expr -> Expr) -> ([Expr] -> Expr) -> [Expr] -> Expr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expr -> [Expr] -> Expr
forall a. a -> [a] -> a
headOr Expr
forall a. a
err ([Expr] -> Expr) -> [Expr] -> Expr
forall a b. (a -> b) -> a -> b
$ (Expr -> Maybe Expr) -> [Expr] -> [Expr]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Expr -> Expr -> Maybe Expr
$$ Expr
e1)
  [ Expr
consInt
  , Expr
consBool
  , Expr
consChar
  , String -> Cons (Maybe Int) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
":" ((:) :: Cons (Maybe Int))
  ]
  where
  err :: a
err  =  String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"(-:-): unhandled type " String -> String -> String
forall a. [a] -> [a] -> [a]
++ TypeRep -> String
forall a. Show a => a -> String
show (Expr -> TypeRep
typ Expr
e1)
infixr 5 -:-

-- | Append for list of 'Int's encoded as an 'Expr'.
appendInt :: Expr
appendInt :: Expr
appendInt  =  String -> ([Int] -> [Int] -> [Int]) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"++" ([Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
(++) :: [Int] -> [Int] -> [Int])

-- | List concatenation lifted over the 'Expr' type.
--   Works for the element types 'Int', 'Char' and 'Bool'.
--
-- > > (zero -:- one -:- nil) -:- (two -:- three -:- nil)
-- > [0,1] -++- [2,3] :: [Int]
--
-- > > (bee -:- unit cee) -:- unit dee
-- > "bc" -++- "c" :: [Char]
(-++-) :: Expr -> Expr -> Expr
Expr
e1 -++- :: Expr -> Expr -> Expr
-++- Expr
e2 = (Expr -> Expr -> Expr
:$ Expr
e2) (Expr -> Expr) -> ([Expr] -> Expr) -> [Expr] -> Expr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expr -> [Expr] -> Expr
forall a. a -> [a] -> a
headOr Expr
forall a. a
err ([Expr] -> Expr) -> [Expr] -> Expr
forall a b. (a -> b) -> a -> b
$ (Expr -> Maybe Expr) -> [Expr] -> [Expr]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Expr -> Expr -> Maybe Expr
$$ Expr
e1)
  [ String -> ([Int] -> [Int] -> [Int]) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"++" ([Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
(++) :: [Int] -> [Int] -> [Int])
  , String -> (String -> String -> String) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"++" (String -> String -> String
forall a. [a] -> [a] -> [a]
(++) :: String -> String -> String)
  , String -> ([Bool] -> Id [Bool]) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"++" ([Bool] -> Id [Bool]
forall a. [a] -> [a] -> [a]
(++) :: [Bool] -> [Bool] -> [Bool])
  ]
  where
  err :: a
err  =  String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"(-++-): unhandled type " String -> String -> String
forall a. [a] -> [a] -> [a]
++ TypeRep -> String
forall a. Show a => a -> String
show (Expr -> TypeRep
typ Expr
e1)
infixr 5 -++-

-- | List 'head' lifted over the 'Expr' type.
--   Works for the element types 'Int', 'Char' and 'Bool'.
--
-- > > head' $ unit one
-- > head [1] :: Int
--
-- > > head' $ unit bee
-- > head "b" :: Char
--
-- > > head' $ zero -:- unit two
-- > head [0,2] :: Int
--
-- > > evl $ head' $ unit one :: Int
-- > 1
head' :: Expr -> Expr
head' :: Expr -> Expr
head' Expr
exs = Expr -> [Expr] -> Expr
forall a. a -> [a] -> a
headOr Expr
forall a. a
err ([Expr] -> Expr) -> [Expr] -> Expr
forall a b. (a -> b) -> a -> b
$ (Expr -> Maybe Expr) -> [Expr] -> [Expr]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Expr -> Expr -> Maybe Expr
$$ Expr
exs)
  [ String -> ([Int] -> Int) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"head" ([Int] -> Int
forall a. [a] -> a
head :: [Int] -> Int)
  , String -> (String -> Char) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"head" (String -> Char
forall a. [a] -> a
head :: [Char] -> Char)
  , String -> ([Bool] -> Bool) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"head" ([Bool] -> Bool
forall a. [a] -> a
head :: [Bool] -> Bool)
  ]
  where
  err :: a
err  =  String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"head': cannot apply `head :: [a] -> a` to `" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Expr -> String
forall a. Show a => a -> String
show Expr
exs String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"'."

-- | List 'tail' lifted over the 'Expr' type.
--   Works for the element types 'Int', 'Char' and 'Bool'.
--
-- > > tail' $ unit one
-- > tail [1] :: [Int]
--
-- > > tail' $ unit bee
-- > tail "b" :: [Char]
--
-- > > tail' $ zero -:- unit two
-- > tail [0,2] :: [Int]
--
-- > > evl $ tail' $ zero -:- unit two :: [Int]
-- > [2]
tail' :: Expr -> Expr
tail' :: Expr -> Expr
tail' Expr
exs = Expr -> [Expr] -> Expr
forall a. a -> [a] -> a
headOr Expr
forall a. a
err ([Expr] -> Expr) -> [Expr] -> Expr
forall a b. (a -> b) -> a -> b
$ (Expr -> Maybe Expr) -> [Expr] -> [Expr]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Expr -> Expr -> Maybe Expr
$$ Expr
exs)
  [ String -> ([Int] -> [Int]) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"tail" ([Int] -> [Int]
forall a. [a] -> [a]
tail :: [Int] -> [Int])
  , String -> (String -> String) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"tail" (String -> String
forall a. [a] -> [a]
tail :: [Char] -> [Char])
  , String -> Id [Bool] -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"tail" (Id [Bool]
forall a. [a] -> [a]
tail :: [Bool] -> [Bool])
  ]
  where
  err :: a
err  =  String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"tail': unhandled type " String -> String -> String
forall a. [a] -> [a] -> [a]
++ TypeRep -> String
forall a. Show a => a -> String
show (Expr -> TypeRep
typ Expr
exs)

-- | List 'null' lifted over the 'Expr' type.
--   Works for the element types 'Int', 'Char' and 'Bool'.
--
-- > > null' $ unit one
-- > null [1] :: Bool
--
-- > > null' $ nil
-- > null [] :: Bool
--
-- > > evl $ null' nil :: Bool
-- > True
null' :: Expr -> Expr
null' :: Expr -> Expr
null' Expr
exs = Expr -> [Expr] -> Expr
forall a. a -> [a] -> a
headOr Expr
forall a. a
err ([Expr] -> Expr) -> [Expr] -> Expr
forall a b. (a -> b) -> a -> b
$ (Expr -> Maybe Expr) -> [Expr] -> [Expr]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Expr -> Expr -> Maybe Expr
$$ Expr
exs)
  [ String -> ([Int] -> Bool) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"null" ([Int] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null :: [Int] -> Bool)
  , String -> (String -> Bool) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"null" (String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null :: [Char] -> Bool)
  , String -> ([Bool] -> Bool) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"null" ([Bool] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null :: [Bool] -> Bool)
  ]
  where
  err :: a
err  =  String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"null': unhandled type " String -> String -> String
forall a. [a] -> [a] -> [a]
++ TypeRep -> String
forall a. Show a => a -> String
show (Expr -> TypeRep
typ Expr
exs)

-- | List 'length' lifted over the 'Expr' type.
--   Works for the element types 'Int', 'Char' and 'Bool'.
--
-- > > length' $ unit one
-- > length [1] :: Int
--
-- > > length' $ unit bee
-- > length "b" :: Int
--
-- > > length' $ zero -:- unit two
-- > length [0,2] :: Int
--
-- > > evl $ length' $ unit one :: Int
-- > 1
length' :: Expr -> Expr
length' :: Expr -> Expr
length' Expr
exs = Expr -> [Expr] -> Expr
forall a. a -> [a] -> a
headOr Expr
forall a. a
err ([Expr] -> Expr) -> [Expr] -> Expr
forall a b. (a -> b) -> a -> b
$ (Expr -> Maybe Expr) -> [Expr] -> [Expr]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Expr -> Expr -> Maybe Expr
$$ Expr
exs)
  [ String -> ([Int] -> Int) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"length" ([Int] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length :: [Int] -> Int)
  , String -> (String -> Int) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"length" (String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length :: [Char] -> Int)
  , String -> ([Bool] -> Int) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"length" ([Bool] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length :: [Bool] -> Int)
  ]
  where
  err :: a
err  =  String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"length': cannot apply `length :: [a] -> a` to `" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Expr -> String
forall a. Show a => a -> String
show Expr
exs String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"'."

-- | List 'sort' lifted over the 'Expr' type.
--   Works for the element types 'Int', 'Char' and 'Bool'.
--
-- > > sort' $ unit one
-- > sort [1] :: Int
--
-- > > sort' $ unit bee
-- > sort "b" :: Int
--
-- > > sort' $ zero -:- unit two
-- > sort [0,2] :: Int
--
-- > > evl $ sort' $ two -:- unit one :: [Int]
-- > [1,2]
sort' :: Expr -> Expr
sort' :: Expr -> Expr
sort' Expr
exs = Expr -> [Expr] -> Expr
forall a. a -> [a] -> a
headOr Expr
forall a. a
err ([Expr] -> Expr) -> [Expr] -> Expr
forall a b. (a -> b) -> a -> b
$ (Expr -> Maybe Expr) -> [Expr] -> [Expr]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Expr -> Expr -> Maybe Expr
$$ Expr
exs)
  [ String -> ([Int] -> [Int]) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"sort" ([Int] -> [Int]
forall a. Ord a => [a] -> [a]
sort :: [Int] -> [Int])
  , String -> (String -> String) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"sort" (String -> String
forall a. Ord a => [a] -> [a]
sort :: [Char] -> [Char])
  , String -> Id [Bool] -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"sort" (Id [Bool]
forall a. Ord a => [a] -> [a]
sort :: [Bool] -> [Bool])
  ]
  where
  err :: a
err  =  String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"sort': unhandled type " String -> String -> String
forall a. [a] -> [a] -> [a]
++ TypeRep -> String
forall a. Show a => a -> String
show (Expr -> TypeRep
typ Expr
exs)

-- | List 'insert' lifted over the 'Expr' type.
--   Works for the element types 'Int', 'Char' and 'Bool'.
--
-- > > insert' zero nilInt
-- > insert 0 [] :: [Int]
--
-- > > insert' false (false -:- unit true)
-- > insert False [False,True] :: [Bool]
insert' :: Expr -> Expr -> Expr
insert' :: Expr -> Expr -> Expr
insert' Expr
ex Expr
exs  =  (Expr -> Expr -> Expr
:$ Expr
exs) (Expr -> Expr) -> ([Expr] -> Expr) -> [Expr] -> Expr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expr -> [Expr] -> Expr
forall a. a -> [a] -> a
headOr Expr
forall a. a
err ([Expr] -> Expr) -> [Expr] -> Expr
forall a b. (a -> b) -> a -> b
$ (Expr -> Maybe Expr) -> [Expr] -> [Expr]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Expr -> Expr -> Maybe Expr
$$ Expr
ex)
  [ String -> Cons Int -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"insert" (Cons Int
forall a. Ord a => a -> [a] -> [a]
insert :: Int -> [Int] -> [Int])
  , String -> Cons Bool -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"insert" (Cons Bool
forall a. Ord a => a -> [a] -> [a]
insert :: Bool -> [Bool] -> [Bool])
  , String -> Cons Char -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"insert" (Cons Char
forall a. Ord a => a -> [a] -> [a]
insert :: Char -> String -> String)
  ]
  where
  err :: a
err  =  String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"insert': unhandled type " String -> String -> String
forall a. [a] -> [a] -> [a]
++ TypeRep -> String
forall a. Show a => a -> String
show (Expr -> TypeRep
typ Expr
ex)

-- | List 'elem' lifted over the 'Expr' type.
--   Works for the element types 'Int', 'Char' and 'Bool'.
--
-- > > elem' false (false -:- unit true)
-- > elem False [False,True] :: Bool
--
-- > > evl $ elem' false (false -:- unit true) :: Bool
-- > True
elem' :: Expr -> Expr -> Expr
elem' :: Expr -> Expr -> Expr
elem' Expr
ex Expr
exs  =  (Expr -> Expr -> Expr
:$ Expr
exs) (Expr -> Expr) -> ([Expr] -> Expr) -> [Expr] -> Expr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expr -> [Expr] -> Expr
forall a. a -> [a] -> a
headOr Expr
forall a. a
err ([Expr] -> Expr) -> [Expr] -> Expr
forall a b. (a -> b) -> a -> b
$ (Expr -> Maybe Expr) -> [Expr] -> [Expr]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Expr -> Expr -> Maybe Expr
$$ Expr
ex)
  [ String -> (Int -> [Int] -> Bool) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"elem" (Int -> [Int] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem :: Int -> [Int] -> Bool)
  , String -> (Bool -> [Bool] -> Bool) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"elem" (Bool -> [Bool] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem :: Bool -> [Bool] -> Bool)
  , String -> (Char -> String -> Bool) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"elem" (Char -> String -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem :: Char -> String -> Bool)
  ]
  where
  err :: a
err  =  String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"elem': unhandled type " String -> String -> String
forall a. [a] -> [a] -> [a]
++ TypeRep -> String
forall a. Show a => a -> String
show (Expr -> TypeRep
typ Expr
ex)

-- | '$' lifted over 'Expr's
--
-- > > absE -$- one
-- > abs $ 1 :: Int
--
-- Works for 'Int', 'Bool', 'Char' argument types and their lists.
(-$-) :: Expr -> Expr -> Expr
Expr
ef -$- :: Expr -> Expr -> Expr
-$- Expr
ex = (Expr -> Expr -> Expr
:$ Expr
ex) (Expr -> Expr) -> ([Expr] -> Expr) -> [Expr] -> Expr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expr -> [Expr] -> Expr
forall a. a -> [a] -> a
headOr Expr
forall a. a
err ([Expr] -> Expr) -> [Expr] -> Expr
forall a b. (a -> b) -> a -> b
$ (Expr -> Maybe Expr) -> [Expr] -> [Expr]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Expr -> Expr -> Maybe Expr
$$ Expr
ef)
  [ String -> Apply Int -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"$" (Apply Int
forall a b. (a -> b) -> a -> b
($) :: Apply Int)
  , String -> Apply Bool -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"$" (Apply Bool
forall a b. (a -> b) -> a -> b
($) :: Apply Bool)
  , String -> Apply Char -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"$" (Apply Char
forall a b. (a -> b) -> a -> b
($) :: Apply Char)
  , String -> Apply [Int] -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"$" (Apply [Int]
forall a b. (a -> b) -> a -> b
($) :: Apply [Int])
  , String -> Apply [Bool] -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"$" (Apply [Bool]
forall a b. (a -> b) -> a -> b
($) :: Apply [Bool])
  , String -> Apply String -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"$" (Apply String
forall a b. (a -> b) -> a -> b
($) :: Apply [Char])
  ]
  where
  err :: a
err  =  String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"(-$-): unhandled type " String -> String -> String
forall a. [a] -> [a] -> [a]
++ TypeRep -> String
forall a. Show a => a -> String
show (Expr -> TypeRep
typ Expr
ef)
infixl 6 -$-
type Apply a = (a -> a) -> a -> a

-- | Constructs an equation between two 'Expr's.
--
-- > > xx -==- zero
-- > x == 0 :: Bool
--
-- > > cc -==- dee
-- > c == 'd' :: Bool
--
-- This works for the 'Int', 'Bool', 'Char' argument types and their lists.
(-==-) :: Expr -> Expr -> Expr
Expr
ex -==- :: Expr -> Expr -> Expr
-==- Expr
ey  =  (Expr -> Expr -> Expr
:$ Expr
ey) (Expr -> Expr) -> ([Expr] -> Expr) -> [Expr] -> Expr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expr -> [Expr] -> Expr
forall a. a -> [a] -> a
headOr Expr
forall a. a
err ([Expr] -> Expr) -> [Expr] -> Expr
forall a b. (a -> b) -> a -> b
$ (Expr -> Maybe Expr) -> [Expr] -> [Expr]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Expr -> Expr -> Maybe Expr
$$ Expr
ex)
  [ String -> Comparison () -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"==" (Comparison ()
forall a. Eq a => a -> a -> Bool
(==) :: Comparison ())
  , String -> Comparison Int -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"==" (Comparison Int
forall a. Eq a => a -> a -> Bool
(==) :: Comparison Int)
  , String -> (Bool -> Bool -> Bool) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"==" (Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
(==) :: Comparison Bool)
  , String -> Comparison Char -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"==" (Comparison Char
forall a. Eq a => a -> a -> Bool
(==) :: Comparison Char)
  , String -> Comparison [Int] -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"==" (Comparison [Int]
forall a. Eq a => a -> a -> Bool
(==) :: Comparison [Int])
  , String -> Comparison [Bool] -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"==" (Comparison [Bool]
forall a. Eq a => a -> a -> Bool
(==) :: Comparison [Bool])
  , String -> Comparison String -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"==" (Comparison String
forall a. Eq a => a -> a -> Bool
(==) :: Comparison [Char])
  ]
  where
  err :: a
err  =  String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"(-==-): unhandled type " String -> String -> String
forall a. [a] -> [a] -> [a]
++ TypeRep -> String
forall a. Show a => a -> String
show (Expr -> TypeRep
typ Expr
ex)
infix 4 -==-
type Comparison a = a -> a -> Bool

-- | Constructs an inequation between two 'Expr's.
--
-- > > xx -/=- zero
-- > x /= 0 :: Bool
--
-- > > cc -/=- ae
-- > c /= 'a' :: Bool
(-/=-) :: Expr -> Expr -> Expr
Expr
ex -/=- :: Expr -> Expr -> Expr
-/=- Expr
ey  =  (Expr -> Expr -> Expr
:$ Expr
ey) (Expr -> Expr) -> ([Expr] -> Expr) -> [Expr] -> Expr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expr -> [Expr] -> Expr
forall a. a -> [a] -> a
headOr Expr
forall a. a
err ([Expr] -> Expr) -> [Expr] -> Expr
forall a b. (a -> b) -> a -> b
$ (Expr -> Maybe Expr) -> [Expr] -> [Expr]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Expr -> Expr -> Maybe Expr
$$ Expr
ex)
  [ String -> Comparison () -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"/=" (Comparison ()
forall a. Eq a => a -> a -> Bool
(/=) :: Comparison ())
  , String -> Comparison Int -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"/=" (Comparison Int
forall a. Eq a => a -> a -> Bool
(/=) :: Comparison Int)
  , String -> (Bool -> Bool -> Bool) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"/=" (Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
(/=) :: Comparison Bool)
  , String -> Comparison Char -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"/=" (Comparison Char
forall a. Eq a => a -> a -> Bool
(/=) :: Comparison Char)
  , String -> Comparison [Int] -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"/=" (Comparison [Int]
forall a. Eq a => a -> a -> Bool
(/=) :: Comparison [Int])
  , String -> Comparison [Bool] -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"/=" (Comparison [Bool]
forall a. Eq a => a -> a -> Bool
(/=) :: Comparison [Bool])
  , String -> Comparison String -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"/=" (Comparison String
forall a. Eq a => a -> a -> Bool
(/=) :: Comparison [Char])
  ]
  where
  err :: a
err  =  String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"(-/=-): unhandled type " String -> String -> String
forall a. [a] -> [a] -> [a]
++ TypeRep -> String
forall a. Show a => a -> String
show (Expr -> TypeRep
typ Expr
ex)
infix 4 -/=-

-- | Constructs a less-than-or-equal inequation between two 'Expr's.
--
-- > > xx -<=- zero
-- > x <= 0 :: Bool
--
-- > > cc -<=- ae
-- > c <= 'a' :: Bool
(-<=-) :: Expr -> Expr -> Expr
Expr
ex -<=- :: Expr -> Expr -> Expr
-<=- Expr
ey  =  (Expr -> Expr -> Expr
:$ Expr
ey) (Expr -> Expr) -> ([Expr] -> Expr) -> [Expr] -> Expr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expr -> [Expr] -> Expr
forall a. a -> [a] -> a
headOr Expr
forall a. a
err ([Expr] -> Expr) -> [Expr] -> Expr
forall a b. (a -> b) -> a -> b
$ (Expr -> Maybe Expr) -> [Expr] -> [Expr]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Expr -> Expr -> Maybe Expr
$$ Expr
ex)
  [ String -> Comparison () -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"<=" (Comparison ()
forall a. Ord a => a -> a -> Bool
(<=) :: Comparison ())
  , String -> Comparison Int -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"<=" (Comparison Int
forall a. Ord a => a -> a -> Bool
(<=) :: Comparison Int)
  , String -> (Bool -> Bool -> Bool) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"<=" (Bool -> Bool -> Bool
forall a. Ord a => a -> a -> Bool
(<=) :: Comparison Bool)
  , String -> Comparison Char -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"<=" (Comparison Char
forall a. Ord a => a -> a -> Bool
(<=) :: Comparison Char)
  , String -> Comparison [Int] -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"<=" (Comparison [Int]
forall a. Ord a => a -> a -> Bool
(<=) :: Comparison [Int])
  , String -> Comparison [Bool] -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"<=" (Comparison [Bool]
forall a. Ord a => a -> a -> Bool
(<=) :: Comparison [Bool])
  , String -> Comparison String -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"<=" (Comparison String
forall a. Ord a => a -> a -> Bool
(<=) :: Comparison [Char])
  ]
  where
  err :: a
err  =  String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"(-<=-): unhandled type " String -> String -> String
forall a. [a] -> [a] -> [a]
++ TypeRep -> String
forall a. Show a => a -> String
show (Expr -> TypeRep
typ Expr
ex)
infix 4 -<=-

-- | Constructs a less-than inequation between two 'Expr's.
--
-- > > xx -<- zero
-- > x < 0 :: Bool
--
-- > > cc -<- bee
-- > c < 'b' :: Bool
(-<-) :: Expr -> Expr -> Expr
Expr
ex -<- :: Expr -> Expr -> Expr
-<- Expr
ey  =  (Expr -> Expr -> Expr
:$ Expr
ey) (Expr -> Expr) -> ([Expr] -> Expr) -> [Expr] -> Expr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expr -> [Expr] -> Expr
forall a. a -> [a] -> a
headOr Expr
forall a. a
err ([Expr] -> Expr) -> [Expr] -> Expr
forall a b. (a -> b) -> a -> b
$ (Expr -> Maybe Expr) -> [Expr] -> [Expr]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Expr -> Expr -> Maybe Expr
$$ Expr
ex)
  [ String -> Comparison () -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"<" (Comparison ()
forall a. Ord a => a -> a -> Bool
(<) :: Comparison ())
  , String -> Comparison Int -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"<" (Comparison Int
forall a. Ord a => a -> a -> Bool
(<) :: Comparison Int)
  , String -> (Bool -> Bool -> Bool) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"<" (Bool -> Bool -> Bool
forall a. Ord a => a -> a -> Bool
(<) :: Comparison Bool)
  , String -> Comparison Char -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"<" (Comparison Char
forall a. Ord a => a -> a -> Bool
(<) :: Comparison Char)
  , String -> Comparison [Int] -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"<" (Comparison [Int]
forall a. Ord a => a -> a -> Bool
(<) :: Comparison [Int])
  , String -> Comparison [Bool] -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"<" (Comparison [Bool]
forall a. Ord a => a -> a -> Bool
(<) :: Comparison [Bool])
  , String -> Comparison String -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"<" (Comparison String
forall a. Ord a => a -> a -> Bool
(<) :: Comparison [Char])
  ]
  where
  err :: a
err  =  String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"(-<-): unhandled type " String -> String -> String
forall a. [a] -> [a] -> [a]
++ TypeRep -> String
forall a. Show a => a -> String
show (Expr -> TypeRep
typ Expr
ex)
infix 4 -<-

-- | A virtual function @if :: Bool -> a -> a -> a@ lifted over the 'Expr' type.
--   This is displayed as an if-then-else.
--
-- > > if' pp zero xx
-- > (if p then 0 else x) :: Int
--
-- > > zz -*- if' pp xx yy
-- > z * (if p then x else y) :: Int
--
-- > > if' pp false true -||- if' qq true false
-- > (if p then False else True) || (if q then True else False) :: Bool
--
-- > > evl $ if' true (val 't') (val 'f') :: Char
-- > 't'
if' :: Expr -> Expr -> Expr -> Expr
if' :: Expr -> Expr -> Expr -> Expr
if' Expr
ep Expr
ex Expr
ey  =  (Expr -> Expr -> Expr
:$ Expr
ey) (Expr -> Expr) -> ([Expr] -> Expr) -> [Expr] -> Expr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expr -> [Expr] -> Expr
forall a. a -> [a] -> a
headOr Expr
forall a. a
err ([Expr] -> Expr) -> ([Expr] -> [Expr]) -> [Expr] -> Expr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Expr -> Maybe Expr) -> [Expr] -> [Expr]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Expr -> Expr -> Maybe Expr
$$ Expr
ex) ([Expr] -> Expr) -> [Expr] -> Expr
forall a b. (a -> b) -> a -> b
$ (Expr -> Expr) -> [Expr] -> [Expr]
forall a b. (a -> b) -> [a] -> [b]
map (Expr -> Expr -> Expr
:$ Expr
ep)
  [ String -> If () -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"if" (If ()
forall a. Bool -> a -> a -> a
iff :: If ())
  , String -> If Int -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"if" (If Int
forall a. Bool -> a -> a -> a
iff :: If Int)
  , String -> If Bool -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"if" (If Bool
forall a. Bool -> a -> a -> a
iff :: If Bool)
  , String -> If Char -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"if" (If Char
forall a. Bool -> a -> a -> a
iff :: If Char)
  , String -> If [Int] -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"if" (If [Int]
forall a. Bool -> a -> a -> a
iff :: If [Int])
  , String -> If [Bool] -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"if" (If [Bool]
forall a. Bool -> a -> a -> a
iff :: If [Bool])
  , String -> If String -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"if" (If String
forall a. Bool -> a -> a -> a
iff :: If [Char])
  ]
  where
  err :: a
err  =  String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"if': unhandled type " String -> String -> String
forall a. [a] -> [a] -> [a]
++ TypeRep -> String
forall a. Show a => a -> String
show (Expr -> TypeRep
typ Expr
ex)
  iff :: Bool -> a -> a -> a
  iff :: Bool -> a -> a -> a
iff Bool
p a
x a
y  =  if Bool
p then a
x else a
y
type If a = Bool -> a -> a -> a

-- | Constructs an 'Expr'-encoded 'compare' operation between two 'Expr's.
--
-- > > xx `compare'` zero
-- > compare x 0 :: Ordering
--
-- > > compare' ae bee
-- > compare 'a' 'b' :: Ordering
compare' :: Expr -> Expr -> Expr
compare' :: Expr -> Expr -> Expr
compare' Expr
ex Expr
ey  =  (Expr -> Expr -> Expr
:$ Expr
ey) (Expr -> Expr) -> ([Expr] -> Expr) -> [Expr] -> Expr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expr -> [Expr] -> Expr
forall a. a -> [a] -> a
headOr Expr
forall a. a
err ([Expr] -> Expr) -> [Expr] -> Expr
forall a b. (a -> b) -> a -> b
$ (Expr -> Maybe Expr) -> [Expr] -> [Expr]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Expr -> Expr -> Maybe Expr
$$ Expr
ex)
  [ String -> Compare () -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"compare" (Compare ()
forall a. Ord a => a -> a -> Ordering
compare :: Compare ())
  , String -> Compare Int -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"compare" (Compare Int
forall a. Ord a => a -> a -> Ordering
compare :: Compare Int)
  , String -> Compare Bool -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"compare" (Compare Bool
forall a. Ord a => a -> a -> Ordering
compare :: Compare Bool)
  , String -> Compare Char -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"compare" (Compare Char
forall a. Ord a => a -> a -> Ordering
compare :: Compare Char)
  , String -> Compare [Int] -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"compare" (Compare [Int]
forall a. Ord a => a -> a -> Ordering
compare :: Compare [Int])
  , String -> Compare [Bool] -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"compare" (Compare [Bool]
forall a. Ord a => a -> a -> Ordering
compare :: Compare [Bool])
  , String -> Compare String -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"compare" (Compare String
forall a. Ord a => a -> a -> Ordering
compare :: Compare [Char])
  ]
  where
  err :: a
err  =  String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"(-<-): unhandled type " String -> String -> String
forall a. [a] -> [a] -> [a]
++ TypeRep -> String
forall a. Show a => a -> String
show (Expr -> TypeRep
typ Expr
ex)
type Compare a = a -> a -> Ordering

-- | 'Nothing' bound to the 'Maybe' 'Int' type encoded as an 'Expr'.
--
-- This is an alias to 'nothingInt'.
nothing :: Expr
nothing :: Expr
nothing  =  Expr
nothingInt

-- | 'Nothing' bound to the 'Maybe' 'Int' type encoded as an 'Expr'.
nothingInt :: Expr
nothingInt :: Expr
nothingInt   =  Maybe Int -> Expr
forall a. (Typeable a, Show a) => a -> Expr
val (Maybe Int
forall a. Maybe a
Nothing :: Maybe Int)

-- | 'Nothing' bound to the 'Maybe' 'Bool' type encoded as an 'Expr'.
nothingBool :: Expr
nothingBool :: Expr
nothingBool  =  Maybe Bool -> Expr
forall a. (Typeable a, Show a) => a -> Expr
val (Maybe Bool
forall a. Maybe a
Nothing :: Maybe Bool)

-- | The 'Just' constructor of the 'Int' element type encoded as an 'Expr'.
justInt :: Expr
justInt :: Expr
justInt      =  String -> (Int -> Maybe Int) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"Just" (Int -> Maybe Int
forall a. a -> Maybe a
Just :: Int -> Maybe Int)

-- | The 'Just' constructor of the 'Bool' element type encoded as an 'Expr'.
justBool :: Expr
justBool :: Expr
justBool     =  String -> (Bool -> Maybe Bool) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"Just" (Bool -> Maybe Bool
forall a. a -> Maybe a
Just :: Bool -> Maybe Bool)

-- | The 'Just' constructor lifted over the 'Expr' type.
--
-- This works for the 'Bool' and 'Int' argument types.
--
-- > > just zero
-- > Just 0 :: Maybe Int
-- > > just false
-- > Just False :: Maybe Bool
just :: Expr -> Expr
just :: Expr -> Expr
just Expr
ex  =  Expr -> [Expr] -> Expr
forall a. a -> [a] -> a
headOr Expr
forall a. a
err ([Expr] -> Expr) -> [Expr] -> Expr
forall a b. (a -> b) -> a -> b
$ (Expr -> Maybe Expr) -> [Expr] -> [Expr]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Expr -> Expr -> Maybe Expr
$$ Expr
ex)
  [ Expr
justInt
  , Expr
justBool
  ]
  where
  err :: a
err  =  String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"just: unhandled type " String -> String -> String
forall a. [a] -> [a] -> [a]
++ TypeRep -> String
forall a. Show a => a -> String
show (Expr -> TypeRep
typ Expr
ex)

-- | An infix synonym of 'pair'.
(-|-) :: Expr -> Expr -> Expr
-|- :: Expr -> Expr -> Expr
(-|-) = Expr -> Expr -> Expr
pair

-- | The pair constructor lifted over 'Expr's.
--
-- This works for the 'Int' and 'Bool' element types
-- by differently from 'foldPair' by returning a well-typed expression.
pair :: Expr -> Expr -> Expr
pair :: Expr -> Expr -> Expr
pair Expr
x Expr
y  =  Expr
comma Expr -> Expr -> Expr
:$ Expr
x Expr -> Expr -> Expr
:$ Expr
y
  where
  comma :: Expr
comma  =  case (TypeRep -> String
forall a. Show a => a -> String
show (TypeRep -> String) -> TypeRep -> String
forall a b. (a -> b) -> a -> b
$ Expr -> TypeRep
typ Expr
x, TypeRep -> String
forall a. Show a => a -> String
show (TypeRep -> String) -> TypeRep -> String
forall a b. (a -> b) -> a -> b
$ Expr -> TypeRep
typ Expr
y) of
            (String
"Int", String
"Int")  -> String -> Pair Int Int -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"," ((,) :: Pair Int Int)
            (String
"Int", String
"Bool") -> String -> Pair Int Bool -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"," ((,) :: Pair Int Bool)
            (String
"Bool",String
"Int")  -> String -> Pair Bool Int -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"," ((,) :: Pair Bool Int)
            (String
"Bool",String
"Bool") -> String -> Pair Bool Bool -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"," ((,) :: Pair Bool Bool)
            (String
t,String
t')          -> String -> Expr
forall a. HasCallStack => String -> a
error (String -> Expr) -> String -> Expr
forall a b. (a -> b) -> a -> b
$ String
"(-:-): unhandled types " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
t String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
t'
type Pair a b = a -> b -> (a,b)

-- | The pair constructor (@ :: ... -> (Int,Int) @) encoded as an 'Expr'.
comma :: Expr
comma :: Expr
comma = String -> Pair Int Int -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"," ((,) :: Pair Int Int)

-- | The triple/trio constructor lifted over 'Expr's.
--
-- This only works for the 'Int' element type.
triple :: Expr -> Expr -> Expr -> Expr
triple :: Expr -> Expr -> Expr -> Expr
triple Expr
e1 Expr
e2 Expr
e3 = Expr
ccE Expr -> Expr -> Expr
:$ Expr
e1 Expr -> Expr -> Expr
:$ Expr
e2 Expr -> Expr -> Expr
:$ Expr
e3
  where
  ccE :: Expr
ccE = String -> (Int -> Int -> Int -> (Int, Int, Int)) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
",," ((,,) :: Int -> Int -> Int -> (Int,Int,Int))

-- | The quadruple constructor lifted over 'Expr's.
--
-- This only works for the 'Int' element type.
quadruple :: Expr -> Expr -> Expr -> Expr -> Expr
quadruple :: Expr -> Expr -> Expr -> Expr -> Expr
quadruple Expr
e1 Expr
e2 Expr
e3 Expr
e4 = Expr
cccE Expr -> Expr -> Expr
:$ Expr
e1 Expr -> Expr -> Expr
:$ Expr
e2 Expr -> Expr -> Expr
:$ Expr
e3 Expr -> Expr -> Expr
:$ Expr
e4
  where
  cccE :: Expr
cccE = String
-> (Int -> Int -> Int -> Int -> (Int, Int, Int, Int)) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
",,," ((,,,) :: Int -> Int -> Int -> Int -> (Int,Int,Int,Int))

-- | The quintuple constructor lifted over 'Expr's.
--
-- This only works for the 'Int' element type.
quintuple :: Expr -> Expr -> Expr -> Expr -> Expr -> Expr
quintuple :: Expr -> Expr -> Expr -> Expr -> Expr -> Expr
quintuple Expr
e1 Expr
e2 Expr
e3 Expr
e4 Expr
e5 = Expr
ccccE Expr -> Expr -> Expr
:$ Expr
e1 Expr -> Expr -> Expr
:$ Expr
e2 Expr -> Expr -> Expr
:$ Expr
e3 Expr -> Expr -> Expr
:$ Expr
e4 Expr -> Expr -> Expr
:$ Expr
e5
  where
  ccccE :: Expr
ccccE = String
-> (Int -> Int -> Int -> Int -> Int -> (Int, Int, Int, Int, Int))
-> Expr
forall a. Typeable a => String -> a -> Expr
value String
",,,," ((,,,,) :: Int -> Int -> Int -> Int -> Int -> (Int,Int,Int,Int,Int))

-- | The sixtuple constructor lifted over 'Expr's.
--
-- This only works for the 'Int' element type.
sixtuple :: Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr
sixtuple :: Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr
sixtuple Expr
e1 Expr
e2 Expr
e3 Expr
e4 Expr
e5 Expr
e6 = Expr
cccccE Expr -> Expr -> Expr
:$ Expr
e1 Expr -> Expr -> Expr
:$ Expr
e2 Expr -> Expr -> Expr
:$ Expr
e3 Expr -> Expr -> Expr
:$ Expr
e4 Expr -> Expr -> Expr
:$ Expr
e5 Expr -> Expr -> Expr
:$ Expr
e6
  where
  cccccE :: Expr
cccccE = String
-> (Int
    -> Int
    -> Int
    -> Int
    -> Int
    -> Int
    -> (Int, Int, Int, Int, Int, Int))
-> Expr
forall a. Typeable a => String -> a -> Expr
value String
",,,,," ((,,,,,) :: Int -> Int -> Int -> Int -> Int -> Int -> (Int,Int,Int,Int,Int,Int))

-- | A typed hole of @[Bool]@ type encoded as an 'Expr'.
--
-- > > bs_
-- > _ :: [Bool]
bs_ :: Expr
bs_ :: Expr
bs_  =  [Bool] -> Expr
forall a. Typeable a => a -> Expr
hole [Bool
bool]

-- | 'Expr' representing a variable @p' :: `[Bool]`@.
--
-- > > pps
-- > ps :: [Bool]
pps :: Expr
pps :: Expr
pps  =  String -> [Bool] -> Expr
forall a. Typeable a => String -> a -> Expr
var String
"ps" [Bool
bool]

-- | A typed hole of '[Bool]' type
--
-- > > qqs
-- > qs :: [Bool]
qqs :: Expr
qqs :: Expr
qqs  =  String -> [Bool] -> Expr
forall a. Typeable a => String -> a -> Expr
var String
"qs" [Bool
bool]

-- | 'and' lifted over the 'Expr' type.
--
-- > > and' pps
-- > and ps :: Bool
--
-- > > evl (and' $ expr [False,True]) :: Bool
-- > False
and' :: Expr -> Expr
and' :: Expr -> Expr
and' Expr
e  =  Expr
andE Expr -> Expr -> Expr
:$ Expr
e
  where
  andE :: Expr
andE  =  String -> ([Bool] -> Bool) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"and" ([Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
and :: [Bool] -> Bool)

-- | 'or' lifted over the 'Expr' type.
--
-- > > or' pps
-- > or ps :: Bool
--
-- > > evl (or' $ expr [False,True]) :: Bool
-- > True
or' :: Expr -> Expr
or' :: Expr -> Expr
or' Expr
e  =  Expr
orE Expr -> Expr -> Expr
:$ Expr
e
  where
  orE :: Expr
orE  =  String -> ([Bool] -> Bool) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"or" ([Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
or :: [Bool] -> Bool)

-- | 'sum' of 'Int' elements lifted over the 'Expr' type.
--
-- > > sum' xxs
-- > sum xs :: Int
--
-- > > evl (sum' $ expr [1,2,3::Int]) :: Int
-- > 6
sum' :: Expr -> Expr
sum' :: Expr -> Expr
sum' Expr
e  =  Expr
sumE Expr -> Expr -> Expr
:$ Expr
e
  where
  sumE :: Expr
sumE  =  String -> ([Int] -> Int) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"sum" ([Int] -> Int
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum :: [Int] -> Int)

-- | 'product' of 'Int' elements lifted over the 'Expr' type.
--
-- > > product' xxs
-- > product xs :: Int
--
-- > > evl (product' $ expr [1,2,3::Int]) :: Int
-- > 6
product' :: Expr -> Expr
product' :: Expr -> Expr
product' Expr
e  =  Expr
productE Expr -> Expr -> Expr
:$ Expr
e
  where
  productE :: Expr
productE  =  String -> ([Int] -> Int) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"product" ([Int] -> Int
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
product :: [Int] -> Int)

headOr :: a -> [a] -> a
headOr :: a -> [a] -> a
headOr a
x []     =  a
x
headOr a
_ (a
x:[a]
_)  =  a
x

-- | Function composition encoded as an 'Expr':
--
-- > > compose
-- > (.) :: (Int -> Int) -> (Int -> Int) -> Int -> Int
compose :: Expr
compose :: Expr
compose  =  String -> Compose Int -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"." (Compose Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) :: Compose Int)

-- | Function composition '.' lifted over 'Expr'.
--
-- > > absE -.- negateE
-- > abs . negate :: Int -> Int
--
-- > > absE -.- negateE :$ one
-- > (abs . negate) 1 :: Int
--
-- This works for 'Int', 'Bool', 'Char' and their lists.
(-.-) :: Expr -> Expr -> Expr
Expr
ex -.- :: Expr -> Expr -> Expr
-.- Expr
ey  =  (Expr -> Expr -> Expr
:$ Expr
ey) (Expr -> Expr) -> ([Expr] -> Expr) -> [Expr] -> Expr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expr -> [Expr] -> Expr
forall a. a -> [a] -> a
headOr Expr
forall a. a
err ([Expr] -> Expr) -> [Expr] -> Expr
forall a b. (a -> b) -> a -> b
$ (Expr -> Maybe Expr) -> [Expr] -> [Expr]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Expr -> Expr -> Maybe Expr
$$ Expr
ex)
  [ String -> Compose () -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"." (Compose ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) :: Compose ())
  , String -> Compose Int -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"." (Compose Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) :: Compose Int)
  , String -> Compose Bool -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"." (Compose Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) :: Compose Bool)
  , String -> Compose Char -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"." (Compose Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) :: Compose Char)
  , String -> Compose [Int] -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"." (Compose [Int]
forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) :: Compose [Int])
  , String -> Compose [Bool] -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"." (Compose [Bool]
forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) :: Compose [Bool])
  , String -> Compose String -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"." (Compose String
forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) :: Compose [Char])
  ]
  where
  err :: a
err  =  String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"(-.-): unhandled type " String -> String -> String
forall a. [a] -> [a] -> [a]
++ TypeRep -> String
forall a. Show a => a -> String
show (Expr -> TypeRep
typ Expr
ex)
type Compose a = (a -> a) -> (a -> a) -> (a -> a)

-- | 'map' over the 'Int' element type encoded as an 'Expr'
--
-- > > mapE
-- > map :: (Int -> Int) -> [Int] -> [Int]
mapE :: Expr
mapE :: Expr
mapE  =  String -> Map Int -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"map" (Map Int
forall a b. (a -> b) -> [a] -> [b]
map :: Map Int)

-- | 'map' lifted over 'Expr's.
--
-- > > map' absE (unit one)
-- > map abs [1] :: [Int]
map' :: Expr -> Expr -> Expr
map' :: Expr -> Expr -> Expr
map' Expr
ef Expr
exs  =  (Expr -> Expr -> Expr
:$ Expr
exs) (Expr -> Expr) -> ([Expr] -> Expr) -> [Expr] -> Expr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expr -> [Expr] -> Expr
forall a. a -> [a] -> a
headOr Expr
forall a. a
err ([Expr] -> Expr) -> [Expr] -> Expr
forall a b. (a -> b) -> a -> b
$ (Expr -> Maybe Expr) -> [Expr] -> [Expr]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Expr -> Expr -> Maybe Expr
$$ Expr
ef)
  [ String -> Map () -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"map" (Map ()
forall a b. (a -> b) -> [a] -> [b]
map :: Map ())
  , String -> Map Int -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"map" (Map Int
forall a b. (a -> b) -> [a] -> [b]
map :: Map Int)
  , String -> Map Bool -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"map" (Map Bool
forall a b. (a -> b) -> [a] -> [b]
map :: Map Bool)
  , String -> Map Char -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"map" (Map Char
forall a b. (a -> b) -> [a] -> [b]
map :: Map Char)
  , String -> Map [Int] -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"map" (Map [Int]
forall a b. (a -> b) -> [a] -> [b]
map :: Map [Int])
  , String -> Map [Bool] -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"map" (Map [Bool]
forall a b. (a -> b) -> [a] -> [b]
map :: Map [Bool])
  , String -> Map String -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"map" (Map String
forall a b. (a -> b) -> [a] -> [b]
map :: Map [Char])
  ]
  where
  err :: a
err  =  String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"map': unhandled type " String -> String -> String
forall a. [a] -> [a] -> [a]
++ TypeRep -> String
forall a. Show a => a -> String
show (Expr -> TypeRep
typ Expr
ef)
type Map a = (a -> a) -> [a] -> [a]

-- | 'enumFrom' lifted over 'Expr's.
--
-- > > enumFrom' zero
-- > enumFrom 0 :: [Int]
--
-- Works for 'Int's, 'Bool's and 'Char's.
enumFrom' :: Expr -> Expr
enumFrom' :: Expr -> Expr
enumFrom' Expr
ex  =  Expr -> [Expr] -> Expr
forall a. a -> [a] -> a
headOr Expr
forall a. a
err ([Expr] -> Expr) -> [Expr] -> Expr
forall a b. (a -> b) -> a -> b
$ (Expr -> Maybe Expr) -> [Expr] -> [Expr]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Expr -> Expr -> Maybe Expr
$$ Expr
ex)
  [ String -> EnumFrom Int -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"enumFrom" (EnumFrom Int
forall a. Enum a => a -> [a]
enumFrom :: EnumFrom Int)
  , String -> EnumFrom Bool -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"enumFrom" (EnumFrom Bool
forall a. Enum a => a -> [a]
enumFrom :: EnumFrom Bool)
  , String -> EnumFrom Char -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"enumFrom" (EnumFrom Char
forall a. Enum a => a -> [a]
enumFrom :: EnumFrom Char)
  ]
  where
  err :: a
err  =  String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"enumFrom': unhandled type " String -> String -> String
forall a. [a] -> [a] -> [a]
++ TypeRep -> String
forall a. Show a => a -> String
show (Expr -> TypeRep
typ Expr
ex)
type EnumFrom a  =  (a -> [a])

-- | 'enumFrom' lifted over 'Expr's named as @".."@ for pretty-printing.
--
-- > > (-..) one
-- > [1..] :: [Int]
--
-- Works for 'Int's, 'Bool's and 'Char's.
(-..) :: Expr -> Expr
-.. :: Expr -> Expr
(-..) Expr
ex  =  Expr -> [Expr] -> Expr
forall a. a -> [a] -> a
headOr Expr
forall a. a
err ([Expr] -> Expr) -> [Expr] -> Expr
forall a b. (a -> b) -> a -> b
$ (Expr -> Maybe Expr) -> [Expr] -> [Expr]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Expr -> Expr -> Maybe Expr
$$ Expr
ex)
  [ String -> EnumFrom Int -> Expr
forall a. Typeable a => String -> a -> Expr
value String
".." (EnumFrom Int
forall a. Enum a => a -> [a]
enumFrom :: EnumFrom Int)
  , String -> EnumFrom Bool -> Expr
forall a. Typeable a => String -> a -> Expr
value String
".." (EnumFrom Bool
forall a. Enum a => a -> [a]
enumFrom :: EnumFrom Bool)
  , String -> EnumFrom Char -> Expr
forall a. Typeable a => String -> a -> Expr
value String
".." (EnumFrom Char
forall a. Enum a => a -> [a]
enumFrom :: EnumFrom Char)
  ]
  where
  err :: a
err  =  String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"(-..): unhandled type " String -> String -> String
forall a. [a] -> [a] -> [a]
++ TypeRep -> String
forall a. Show a => a -> String
show (Expr -> TypeRep
typ Expr
ex)

-- | 'enumFromTo' lifted over 'Expr's
--
-- > > enumFromTo' zero four
-- > enumFromTo 0 4 :: [Int]
enumFromTo' :: Expr -> Expr -> Expr
enumFromTo' :: Expr -> Expr -> Expr
enumFromTo' Expr
ex Expr
ey  =  (Expr -> Expr -> Expr
:$ Expr
ey) (Expr -> Expr) -> ([Expr] -> Expr) -> [Expr] -> Expr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expr -> [Expr] -> Expr
forall a. a -> [a] -> a
headOr Expr
forall a. a
err ([Expr] -> Expr) -> [Expr] -> Expr
forall a b. (a -> b) -> a -> b
$ (Expr -> Maybe Expr) -> [Expr] -> [Expr]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Expr -> Expr -> Maybe Expr
$$ Expr
ex)
  [ String -> EnumFromTo Int -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"enumFromTo" (EnumFromTo Int
forall a. Enum a => a -> a -> [a]
enumFromTo :: EnumFromTo Int)
  , String -> EnumFromTo Bool -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"enumFromTo" (EnumFromTo Bool
forall a. Enum a => a -> a -> [a]
enumFromTo :: EnumFromTo Bool)
  , String -> EnumFromTo Char -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"enumFromTo" (EnumFromTo Char
forall a. Enum a => a -> a -> [a]
enumFromTo :: EnumFromTo Char)
  ]
  where
  err :: a
err  =  String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"enumFromTo': unhandled type " String -> String -> String
forall a. [a] -> [a] -> [a]
++ TypeRep -> String
forall a. Show a => a -> String
show (Expr -> TypeRep
typ Expr
ex)
type EnumFromTo a  =  (a -> a -> [a])

-- | 'enumFromTo' lifted over 'Expr's but named as @".."@ for pretty-printing.
--
-- > > zero -..- four
-- > [0..4] :: [Int]
(-..-) :: Expr -> Expr -> Expr
Expr
ex -..- :: Expr -> Expr -> Expr
-..- Expr
ey  =  (Expr -> Expr -> Expr
:$ Expr
ey) (Expr -> Expr) -> ([Expr] -> Expr) -> [Expr] -> Expr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expr -> [Expr] -> Expr
forall a. a -> [a] -> a
headOr Expr
forall a. a
err ([Expr] -> Expr) -> [Expr] -> Expr
forall a b. (a -> b) -> a -> b
$ (Expr -> Maybe Expr) -> [Expr] -> [Expr]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Expr -> Expr -> Maybe Expr
$$ Expr
ex)
  [ String -> EnumFromTo Int -> Expr
forall a. Typeable a => String -> a -> Expr
value String
".." (EnumFromTo Int
forall a. Enum a => a -> a -> [a]
enumFromTo :: EnumFromTo Int)
  , String -> EnumFromTo Bool -> Expr
forall a. Typeable a => String -> a -> Expr
value String
".." (EnumFromTo Bool
forall a. Enum a => a -> a -> [a]
enumFromTo :: EnumFromTo Bool)
  , String -> EnumFromTo Char -> Expr
forall a. Typeable a => String -> a -> Expr
value String
".." (EnumFromTo Char
forall a. Enum a => a -> a -> [a]
enumFromTo :: EnumFromTo Char)
  ]
  where
  err :: a
err  =  String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"-..-: unhandled type " String -> String -> String
forall a. [a] -> [a] -> [a]
++ TypeRep -> String
forall a. Show a => a -> String
show (Expr -> TypeRep
typ Expr
ex)

-- | 'enumFromThen' lifted over 'Expr's
--
-- > > enumFromThen' zero ten
-- > enumFromThen 0 10 :: [Int]
enumFromThen' :: Expr -> Expr -> Expr
enumFromThen' :: Expr -> Expr -> Expr
enumFromThen' Expr
ex Expr
ey  =  (Expr -> Expr -> Expr
:$ Expr
ey) (Expr -> Expr) -> ([Expr] -> Expr) -> [Expr] -> Expr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expr -> [Expr] -> Expr
forall a. a -> [a] -> a
headOr Expr
forall a. a
err ([Expr] -> Expr) -> [Expr] -> Expr
forall a b. (a -> b) -> a -> b
$ (Expr -> Maybe Expr) -> [Expr] -> [Expr]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Expr -> Expr -> Maybe Expr
$$ Expr
ex)
  [ String -> EnumFromTo Int -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"enumFromThen" (EnumFromTo Int
forall a. Enum a => a -> a -> [a]
enumFromThen :: EnumFromThen Int)
  , String -> EnumFromTo Bool -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"enumFromThen" (EnumFromTo Bool
forall a. Enum a => a -> a -> [a]
enumFromThen :: EnumFromThen Bool)
  , String -> EnumFromTo Char -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"enumFromThen" (EnumFromTo Char
forall a. Enum a => a -> a -> [a]
enumFromThen :: EnumFromThen Char)
  ]
  where
  err :: a
err  =  String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"enumFromThen': unhandled type " String -> String -> String
forall a. [a] -> [a] -> [a]
++ TypeRep -> String
forall a. Show a => a -> String
show (Expr -> TypeRep
typ Expr
ex)
type EnumFromThen a  =  (a -> a -> [a])

-- | 'enumFromThen' lifted over 'Expr's but named as @",.."@ for pretty printing.
--
-- > > zero -... ten
-- > [0,10..] :: [Int]
(-...) :: Expr -> Expr -> Expr
Expr
ex -... :: Expr -> Expr -> Expr
-... Expr
ey  =  (Expr -> Expr -> Expr
:$ Expr
ey) (Expr -> Expr) -> ([Expr] -> Expr) -> [Expr] -> Expr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expr -> [Expr] -> Expr
forall a. a -> [a] -> a
headOr Expr
forall a. a
err ([Expr] -> Expr) -> [Expr] -> Expr
forall a b. (a -> b) -> a -> b
$ (Expr -> Maybe Expr) -> [Expr] -> [Expr]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Expr -> Expr -> Maybe Expr
$$ Expr
ex)
  [ String -> EnumFromTo Int -> Expr
forall a. Typeable a => String -> a -> Expr
value String
",.." (EnumFromTo Int
forall a. Enum a => a -> a -> [a]
enumFromThen :: EnumFromThen Int)
  , String -> EnumFromTo Bool -> Expr
forall a. Typeable a => String -> a -> Expr
value String
",.." (EnumFromTo Bool
forall a. Enum a => a -> a -> [a]
enumFromThen :: EnumFromThen Bool)
  , String -> EnumFromTo Char -> Expr
forall a. Typeable a => String -> a -> Expr
value String
",.." (EnumFromTo Char
forall a. Enum a => a -> a -> [a]
enumFromThen :: EnumFromThen Char)
  ]
  where
  err :: a
err  =  String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"-..-: unhandled type " String -> String -> String
forall a. [a] -> [a] -> [a]
++ TypeRep -> String
forall a. Show a => a -> String
show (Expr -> TypeRep
typ Expr
ex)

-- | 'enumFromThenTo' lifted over 'Expr's.
--
-- > > enumFromThenTo' zero two ten
-- > enumFromThenTo 0 2 10 :: [Int]
enumFromThenTo' :: Expr -> Expr -> Expr -> Expr
enumFromThenTo' :: Expr -> Expr -> Expr -> Expr
enumFromThenTo' Expr
ex Expr
ey Expr
ez  =  (Expr -> Expr -> Expr
:$ Expr
ez) (Expr -> Expr) -> ([Expr] -> Expr) -> [Expr] -> Expr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Expr -> Expr -> Expr
:$ Expr
ey) (Expr -> Expr) -> ([Expr] -> Expr) -> [Expr] -> Expr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expr -> [Expr] -> Expr
forall a. a -> [a] -> a
headOr Expr
forall a. a
err ([Expr] -> Expr) -> [Expr] -> Expr
forall a b. (a -> b) -> a -> b
$ (Expr -> Maybe Expr) -> [Expr] -> [Expr]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Expr -> Expr -> Maybe Expr
$$ Expr
ex)
  [ String -> EnumFromThenTo Int -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"enumFromThenTo" (EnumFromThenTo Int
forall a. Enum a => a -> a -> a -> [a]
enumFromThenTo :: EnumFromThenTo Int)
  , String -> EnumFromThenTo Bool -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"enumFromThenTo" (EnumFromThenTo Bool
forall a. Enum a => a -> a -> a -> [a]
enumFromThenTo :: EnumFromThenTo Bool)
  , String -> EnumFromThenTo Char -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"enumFromThenTo" (EnumFromThenTo Char
forall a. Enum a => a -> a -> a -> [a]
enumFromThenTo :: EnumFromThenTo Char)
  ]
  where
  err :: a
err  =  String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"enumFromThenTo': unhandled type " String -> String -> String
forall a. [a] -> [a] -> [a]
++ TypeRep -> String
forall a. Show a => a -> String
show (Expr -> TypeRep
typ Expr
ex)
type EnumFromThenTo a  =  (a -> a -> a -> [a])

-- | 'enumFromThenTo' lifted over 'Expr's but named as @",.."@ for pretty-printing.
--
-- > > (zero -...- two) ten
-- > [0,2..10] :: [Int]
(-...-) :: Expr -> Expr -> Expr -> Expr
(Expr
ex -...- :: Expr -> Expr -> Expr -> Expr
-...- Expr
ey) Expr
ez  =  (Expr -> Expr -> Expr
:$ Expr
ez) (Expr -> Expr) -> ([Expr] -> Expr) -> [Expr] -> Expr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Expr -> Expr -> Expr
:$ Expr
ey) (Expr -> Expr) -> ([Expr] -> Expr) -> [Expr] -> Expr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expr -> [Expr] -> Expr
forall a. a -> [a] -> a
headOr Expr
forall a. a
err ([Expr] -> Expr) -> [Expr] -> Expr
forall a b. (a -> b) -> a -> b
$ (Expr -> Maybe Expr) -> [Expr] -> [Expr]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Expr -> Expr -> Maybe Expr
$$ Expr
ex)
  [ String -> EnumFromThenTo Int -> Expr
forall a. Typeable a => String -> a -> Expr
value String
",.." (EnumFromThenTo Int
forall a. Enum a => a -> a -> a -> [a]
enumFromThenTo :: EnumFromThenTo Int)
  , String -> EnumFromThenTo Bool -> Expr
forall a. Typeable a => String -> a -> Expr
value String
",.." (EnumFromThenTo Bool
forall a. Enum a => a -> a -> a -> [a]
enumFromThenTo :: EnumFromThenTo Bool)
  , String -> EnumFromThenTo Char -> Expr
forall a. Typeable a => String -> a -> Expr
value String
",.." (EnumFromThenTo Char
forall a. Enum a => a -> a -> a -> [a]
enumFromThenTo :: EnumFromThenTo Char)
  ]
  where
  err :: a
err  =  String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"-..-: unhandled type " String -> String -> String
forall a. [a] -> [a] -> [a]
++ TypeRep -> String
forall a. Show a => a -> String
show (Expr -> TypeRep
typ Expr
ex)