{-|
    Module      :  Data.Number.ER.RnToRm.UnitDom.Base.Tests.Properties.Compose
    Description :  (testing) properties of enclosure composition
    Copyright   :  (c) 2007-2008 Michal Konecny
    License     :  BSD3

    Maintainer  :  mik@konecny.aow.cz
    Stability   :  experimental
    Portability :  portable
    
    Quickcheck properties of polynomial enclosure composition.
-}
module Data.Number.ER.RnToRm.UnitDom.Base.Tests.Properties.Compose
where

import Data.Number.ER.RnToRm.UnitDom.Base.Tests.Properties.Common

import qualified Data.Number.ER.RnToRm.UnitDom.Base as UFB
import Data.Number.ER.RnToRm.UnitDom.Base.Tests.Generate

import qualified Data.Number.ER.Real.Approx as RA
import qualified Data.Number.ER.BasicTypes.DomainBox as DBox

import Data.Number.ER.BasicTypes
import Data.Number.ER.BasicTypes.Tests.Generate

import Data.Number.ER.Misc

import Test.QuickCheck

prop_enclCompose_ThinEncl_consistent
        sampleE reportFileName
        (Deg10Size10 maxDegree maxSize,
         varSelector,
         (FBEnclThinSize10 (n1,e1)),
         (FBEnclThinSize10 (n2,e2))) =
    compose_encl_consistent
        sampleE reportFileName 
        maxDegree maxSize
        varSelector
        n1 e1 n2 e2

prop_enclCompose_ThickEncl_consistent
        sampleE reportFileName
        (Deg10Size10 maxDegree maxSize,
         varSelector,
         (FBEnclThinSize10 (n1,e1)),
         (FBEnclThickSize10 (n2,e2))) =
    compose_encl_consistent
        sampleE reportFileName 
        maxDegree maxSize
        varSelector
        n1 e1 n2 e2

prop_enclCompose_ParalEncl_consistent
        sampleE reportFileName
        (Deg10Size10 maxDegree maxSize,
         varSelector,
         (FBEnclThinSize10 (n1, e1)),
         (FBEnclParalSize10 (n2,e2))) =
    compose_encl_consistent
        sampleE reportFileName 
        maxDegree maxSize
        varSelector
        n1 e1 n2 e2

compose_encl_consistent 
        sampleE reportFileName 
        maxDegree maxSize 
        varSelector
        e1Id e1@(e1LowNeg, e1High) e2Id e2@(e2LowNeg, e2High) =
--    unsafePrint
--    (
--        "compose_encl_consistent: "
--        ++ "\n e1High = " ++ show e1High
--        ++ "\n substVar = " ++ show substVar
--        ++ "\n e2High = " ++ show e2High
--        ++ "\n e2Low = " ++ show (UFB.neg e2LowNeg)
--        ++ "\n composition = " ++ show resEncl
--        ++ "\n**********************"
--    ) $
    enclAtKeyPointsConsistent
        reportFileName
        ((maxDegree, maxSize), varSelector, e1Id, e2Id)
        composeAtPointInner
        allVars
        resEncl
    where
    _ = [sampleE,e1]
    resEncl = UFB.composeEncl maxDegree maxSize e1High substVar e2
    substVar = e1Vars !! (varSelector `mod` (length e1Vars))
    e1Vars = UFB.getVariables e1High
    allVars = 
        UFB.getVariables $ 
            e1High UFB.+^ e2High UFB.+^ e2Low
            where
            e2Low = UFB.neg e2LowNeg
    composeAtPointInner point =
--        unsafePrintReturn
--        (
--            "\n point = " ++ show point
--            ++ "\n substVar = " ++ show substVar
--            ++ " substVal = " ++ show substVal
--            ++ "\n result = "
--        ) $
        result
        where
        result 
            | RA.isConsistent substVal =
                UFB.evalEnclInner pointWithSubst (UFB.neg e1High, e1High)
            | otherwise =
                RA.toggleConsistency $
                    UFB.evalEncl pointWithSubstReversed (UFB.neg e1High, e1High)
        pointWithSubstReversed =
            DBox.insert substVar (RA.toggleConsistency substVal) point
        pointWithSubst =
            DBox.insert substVar substVal point
        substVal =
            UFB.evalEnclInner point e2