-- |
-- Module      : Conjure.Prim
-- Copyright   : (c) 2021 Rudy Matela
-- License     : 3-Clause BSD  (see the file LICENSE)
-- Maintainer  : Rudy Matela <rudy@matela.com.br>
--
-- This module is part of "Conjure".
--
-- The 'Prim' type and utilities involving it.
--
-- You are probably better off importing "Conjure".
module Conjure.Prim
  ( Prim (..)
  , prim
  , pr
  , prif
  , cjHoles
  , cjTiersFor
  , cjAreEqual
  , cjMkEquation
  )
where

import Conjure.Conjurable
import Conjure.Expr
import Conjure.Utils
import Test.LeanCheck.Error (errorToFalse)
import Test.LeanCheck.Utils
import Test.Speculate.Expr


-- | A primtive expression (paired with instance reification).
type Prim  =  (Expr, Reification)


-- | Provides a primitive value to Conjure.
--   To be used on 'Show' instances.
--   (cf. 'prim')
pr :: (Conjurable a, Show a) => a -> Prim
pr :: a -> Prim
pr a
x  =  (a -> Expr
forall a. (Typeable a, Show a) => a -> Expr
val a
x, a -> Reification
forall a. Conjurable a => a -> Reification
conjureType a
x)


-- | Provides a primitive value to Conjure.
--   To be used on values that are not 'Show' instances
--   such as functions.
--   (cf. 'pr')
prim :: Conjurable a => String -> a -> Prim
prim :: String -> a -> Prim
prim String
s a
x  =  (String -> a -> Expr
forall a. Typeable a => String -> a -> Expr
value String
s a
x, a -> Reification
forall a. Conjurable a => a -> Reification
conjureType a
x)


-- | Provides an if condition bound to the given return type.
prif :: Conjurable a => a -> Prim
prif :: a -> Prim
prif a
x  =  (a -> Expr
forall a. Typeable a => a -> Expr
ifFor a
x, a -> Reification
forall a. Conjurable a => a -> Reification
conjureType a
x)


-- the following functions mirror their "conjure" counterparts from
-- Conjure.Conjurable but need a list of Prims instead of a Conjurable
-- representative.

-- | Computes a list of 'Reification1's from a list of 'Prim's.
--
-- This function mirrors functionality of 'conjureReification'.
cjReification :: [Prim] -> [Reification1]
cjReification :: [Prim] -> [Reification1]
cjReification [Prim]
ps  =  (Reification1 -> Expr) -> Reification
forall b a. Eq b => (a -> b) -> [a] -> [a]
nubOn (\(Expr
eh,Maybe Expr
_,Maybe [[Expr]]
_,[String]
_,Bool
_,Expr
_) -> Expr
eh)
                  Reification -> Reification
forall a b. (a -> b) -> a -> b
$  (Reification -> Reification -> Reification)
-> Reification -> [Reification] -> Reification
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) Reification
forall a. a -> a
id ((Prim -> Reification) -> [Prim] -> [Reification]
forall a b. (a -> b) -> [a] -> [b]
map Prim -> Reification
forall a b. (a, b) -> b
snd [Prim]
ps) [Bool -> Reification1
forall a. Conjurable a => a -> Reification1
conjureReification1 Bool
bool]

-- | Computes a list of holes encoded as 'Expr's from a list of 'Prim's.
--
-- This function mirrors functionality from 'conjureHoles'.
cjHoles :: [Prim] -> [Expr]
cjHoles :: [Prim] -> [Expr]
cjHoles [Prim]
ps  =  [Expr
eh | (Expr
eh,Maybe Expr
_,Just [[Expr]]
_,[String]
_,Bool
_,Expr
_) <- [Prim] -> [Reification1]
cjReification [Prim]
ps]

-- | Computes a function that equates two 'Expr's from a list of 'Prim's.
--
-- This function mirrors functionality from 'conjureMkEquation'.
cjMkEquation :: [Prim] -> Expr -> Expr -> Expr
cjMkEquation :: [Prim] -> Expr -> Expr -> Expr
cjMkEquation [Prim]
ps  =  [Expr] -> Expr -> Expr -> Expr
mkEquation [Expr
eq | (Expr
_,Just Expr
eq,Maybe [[Expr]]
_,[String]
_,Bool
_,Expr
_) <- [Prim] -> [Reification1]
cjReification [Prim]
ps]

-- | Given a list of 'Prim's,
--   computes a function that checks whether two 'Expr's are equal
--   up to a given number of tests.
cjAreEqual :: [Prim] -> Int -> Expr -> Expr -> Bool
cjAreEqual :: [Prim] -> Int -> Expr -> Expr -> Bool
cjAreEqual [Prim]
ps Int
maxTests  =  Expr -> Expr -> Bool
(===)
  where
  -==- :: Expr -> Expr -> Expr
(-==-)  =  [Prim] -> Expr -> Expr -> Expr
cjMkEquation [Prim]
ps
  Expr
e1 === :: Expr -> Expr -> Bool
=== Expr
e2  =  Expr -> Bool
isTrue (Expr -> Bool) -> Expr -> Bool
forall a b. (a -> b) -> a -> b
$ Expr
e1 Expr -> Expr -> Expr
-==- Expr
e2
  isTrue :: Expr -> Bool
isTrue  =  (Expr -> Bool) -> [Expr] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Bool -> Bool
errorToFalse (Bool -> Bool) -> (Expr -> Bool) -> Expr -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Expr -> Bool
forall a. Typeable a => a -> Expr -> a
eval Bool
False) ([Expr] -> Bool) -> (Expr -> [Expr]) -> Expr -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expr -> [Expr]
gs
  gs :: Expr -> [Expr]
gs  =  Int -> [Expr] -> [Expr]
forall a. Int -> [a] -> [a]
take Int
maxTests ([Expr] -> [Expr]) -> (Expr -> [Expr]) -> Expr -> [Expr]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Expr -> [[Expr]]) -> Expr -> [Expr]
grounds ([Prim] -> Expr -> [[Expr]]
cjTiersFor [Prim]
ps)

-- | Given a list of 'Prim's,
--   returns a function that given an 'Expr'
--   will return tiers of test 'Expr' values.
--
-- This is used in 'cjAreEqual'.
cjTiersFor :: [Prim] -> Expr -> [[Expr]]
cjTiersFor :: [Prim] -> Expr -> [[Expr]]
cjTiersFor [Prim]
ps Expr
e  =  [[[Expr]]] -> [[Expr]]
tf [[[Expr]]]
allTiers
  where
  allTiers :: [ [[Expr]] ]
  allTiers :: [[[Expr]]]
allTiers  =  [[[Expr]]
etiers | (Expr
_,Maybe Expr
_,Just [[Expr]]
etiers,[String]
_,Bool
_,Expr
_) <- [Prim] -> [Reification1]
cjReification [Prim]
ps]
  tf :: [[[Expr]]] -> [[Expr]]
tf []  =  [[Expr
e]] -- no tiers found, keep variable
  tf ([[Expr]]
etiers:[[[Expr]]]
etc)  =  case [[Expr]]
etiers of
                      ((Expr
e':[Expr]
_):[[Expr]]
_) | Expr -> TypeRep
typ Expr
e' TypeRep -> TypeRep -> Bool
forall a. Eq a => a -> a -> Bool
== Expr -> TypeRep
typ Expr
e -> [[Expr]]
etiers
                      [[Expr]]
_                            -> [[[Expr]]] -> [[Expr]]
tf [[[Expr]]]
etc