{-# OPTIONS_GHC -Wno-orphans #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE StandaloneDeriving #-}
{-|
    Module      :  AERN2.MP.WithCurrentPrec.Limit
    Description :  WithCurrentPrec limits
    Copyright   :  (c) Michal Konecny
    License     :  BSD3

    Maintainer  :  mikkonecny@gmail.com
    Stability   :  experimental
    Portability :  portable

    WithCurrentPrec limits
-}
module AERN2.MP.WithCurrentPrec.Limit
()
where

import MixedTypesNumPrelude
-- import qualified Prelude as P
-- import Text.Printf

-- import qualified Numeric.CollectErrors as CN

import GHC.TypeLits
import Control.Monad (join)

import AERN2.MP.Ball

import AERN2.Limit

import AERN2.MP.WithCurrentPrec.Type

instance 
    (HasLimits ix (CN MPBall -> CN MPBall)
    , LimitType ix (CN MPBall -> CN MPBall) ~ (CN MPBall -> CN MPBall)
    , KnownNat p)
    => 
    HasLimits ix (WithCurrentPrec p (CN MPBall)) 
    where
    type LimitType ix (WithCurrentPrec p (CN MPBall)) = WithCurrentPrec p (CN MPBall)
    limit :: (ix -> WithCurrentPrec p (CN MPBall))
-> LimitType ix (WithCurrentPrec p (CN MPBall))
limit ix -> WithCurrentPrec p (CN MPBall)
s = forall ix s. HasLimits ix s => (ix -> s) -> LimitType ix s
limit forall a b. (a -> b) -> a -> b
$ forall v. v -> CN v
cn forall b c a. (b -> c) -> (a -> b) -> a -> c
. ix -> WithCurrentPrec p (CN MPBall)
s

instance 
    (HasLimits ix (CN MPBall -> CN MPBall)
    , LimitType ix (CN MPBall -> CN MPBall) ~ (CN MPBall -> CN MPBall)
    , KnownNat p)
    => 
    HasLimits ix (CN (WithCurrentPrec p (CN MPBall)))
    where
    type LimitType ix (CN (WithCurrentPrec p (CN MPBall))) = WithCurrentPrec p (CN MPBall)
    limit :: (ix -> CN (WithCurrentPrec p (CN MPBall)))
-> LimitType ix (CN (WithCurrentPrec p (CN MPBall)))
limit (ix -> CN (WithCurrentPrec p (CN MPBall))
s :: ix -> CN (WithCurrentPrec p (CN MPBall))) = 
        forall {k} (p :: k) t. t -> WithCurrentPrec p t
WithCurrentPrec forall a b. (a -> b) -> a -> b
$ forall ix s. HasLimits ix s => (ix -> s) -> LimitType ix s
limit (ix -> CN MPBall -> CN MPBall
snop) forall a b. (a -> b) -> a -> b
$ CN MPBall
sample
        where
        sample :: CN MPBall
        sample :: CN MPBall
sample = forall t. CanSetPrecision t => Precision -> t -> t
setPrecision (forall (p :: Nat) t. KnownNat p => WithCurrentPrec p t -> Precision
getCurrentPrecision WithCurrentPrec p MPBall
sampleP) (forall v. v -> CN v
cn forall a b. (a -> b) -> a -> b
$ forall t. CanBeMPBall t => t -> MPBall
mpBall Integer
0)
        sampleP :: WithCurrentPrec p MPBall
        sampleP :: WithCurrentPrec p MPBall
sampleP = forall a. HasCallStack => [Char] -> a
error [Char]
"sampleP is not defined, it is only a type proxy"
        snop :: ix -> (CN MPBall -> CN MPBall)
        snop :: ix -> CN MPBall -> CN MPBall
snop ix
ix CN MPBall
_sample = forall (m :: * -> *) a. Monad m => m (m a) -> m a
join forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall {k} (p :: k) t. WithCurrentPrec p t -> t
unWithCurrentPrec forall a b. (a -> b) -> a -> b
$ ix -> CN (WithCurrentPrec p (CN MPBall))
s ix
ix