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

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

    WithCurrentPrec elementary operations
-}
module AERN2.MP.WithCurrentPrec.Elementary
(   
    piCP
    , _example1 , _example2 , _example3
)
where

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

import GHC.TypeLits ( KnownNat )

-- import qualified Numeric.CollectErrors as CN

import AERN2.MP.Ball

import AERN2.MP.WithCurrentPrec.Type

import AERN2.MP.WithCurrentPrec.Field ()

piCP :: (KnownNat p) => WithCurrentPrec (CN MPBall) p
piCP :: WithCurrentPrec (CN MPBall) p
piCP = WithCurrentPrec (CN MPBall) p
r 
    where
    r :: WithCurrentPrec (CN MPBall) p
r = CN MPBall -> WithCurrentPrec (CN MPBall) p
forall k t (p :: k). t -> WithCurrentPrec t p
WithCurrentPrec (CN MPBall -> WithCurrentPrec (CN MPBall) p)
-> CN MPBall -> WithCurrentPrec (CN MPBall) p
forall a b. (a -> b) -> a -> b
$ MPBall -> CN MPBall
forall v. v -> CN v
cn (MPBall -> CN MPBall) -> MPBall -> CN MPBall
forall a b. (a -> b) -> a -> b
$ Precision -> MPBall
piBallP (WithCurrentPrec (CN MPBall) p -> Precision
forall k (p :: k) (proxy :: k -> *).
HasCurrentPrecision p =>
proxy p -> Precision
getCurrentPrecision WithCurrentPrec (CN MPBall) p
r)

instance
    (CanSinCos t)
    =>
    CanSinCos (WithCurrentPrec t p)
    where
    type SinCosType (WithCurrentPrec t p) = WithCurrentPrec (SinCosType t) p
    sin :: WithCurrentPrec t p -> SinCosType (WithCurrentPrec t p)
sin = (t -> SinCosType t)
-> WithCurrentPrec t p -> WithCurrentPrec (SinCosType t) p
forall k t1 t2 (p :: k).
(t1 -> t2) -> WithCurrentPrec t1 p -> WithCurrentPrec t2 p
lift1 t -> SinCosType t
forall t. CanSinCos t => t -> SinCosType t
sin
    cos :: WithCurrentPrec t p -> SinCosType (WithCurrentPrec t p)
cos = (t -> SinCosType t)
-> WithCurrentPrec t p -> WithCurrentPrec (SinCosType t) p
forall k t1 t2 (p :: k).
(t1 -> t2) -> WithCurrentPrec t1 p -> WithCurrentPrec t2 p
lift1 t -> SinCosType t
forall t. CanSinCos t => t -> SinCosType t
cos

instance
    (CanSqrt t)
    =>
    CanSqrt (WithCurrentPrec t p)
    where
    type SqrtType (WithCurrentPrec t p) = WithCurrentPrec (SqrtType t) p
    sqrt :: WithCurrentPrec t p -> SqrtType (WithCurrentPrec t p)
sqrt = (t -> SqrtType t)
-> WithCurrentPrec t p -> WithCurrentPrec (SqrtType t) p
forall k t1 t2 (p :: k).
(t1 -> t2) -> WithCurrentPrec t1 p -> WithCurrentPrec t2 p
lift1 t -> SqrtType t
forall t. CanSqrt t => t -> SqrtType t
sqrt

instance
    (CanExp t)
    =>
    CanExp (WithCurrentPrec t p)
    where
    type ExpType (WithCurrentPrec t p) = WithCurrentPrec (ExpType t) p
    exp :: WithCurrentPrec t p -> ExpType (WithCurrentPrec t p)
exp = (t -> ExpType t)
-> WithCurrentPrec t p -> WithCurrentPrec (ExpType t) p
forall k t1 t2 (p :: k).
(t1 -> t2) -> WithCurrentPrec t1 p -> WithCurrentPrec t2 p
lift1 t -> ExpType t
forall t. CanExp t => t -> ExpType t
exp

instance
    (CanLog t)
    =>
    CanLog (WithCurrentPrec t p)
    where
    type LogType (WithCurrentPrec t p) = WithCurrentPrec (LogType t) p
    log :: WithCurrentPrec t p -> LogType (WithCurrentPrec t p)
log = (t -> LogType t)
-> WithCurrentPrec t p -> WithCurrentPrec (LogType t) p
forall k t1 t2 (p :: k).
(t1 -> t2) -> WithCurrentPrec t1 p -> WithCurrentPrec t2 p
lift1 t -> LogType t
forall t. CanLog t => t -> LogType t
log

instance
    (CanPow t1 t2, p1~p2)
    =>
    (CanPow (WithCurrentPrec t1 p1) (WithCurrentPrec t2 p2)) where
    type PowType (WithCurrentPrec t1 p1) (WithCurrentPrec t2 p2) = WithCurrentPrec (PowType t1 t2) p1
    pow :: WithCurrentPrec t1 p1
-> WithCurrentPrec t2 p2
-> PowType (WithCurrentPrec t1 p1) (WithCurrentPrec t2 p2)
pow = (t1 -> t2 -> PowType t1 t2)
-> WithCurrentPrec t1 p1
-> WithCurrentPrec t2 p2
-> WithCurrentPrec (PowType t1 t2) p1
forall k (p1 :: k) (p2 :: k) t1 t2 t3.
(p1 ~ p2) =>
(t1 -> t2 -> t3)
-> WithCurrentPrec t1 p1
-> WithCurrentPrec t2 p2
-> WithCurrentPrec t3 p1
lift2 t1 -> t2 -> PowType t1 t2
forall b e. CanPow b e => b -> e -> PowType b e
pow

$(declForTypes
  [[t| Integer |], [t| Int |], [t| Rational |]]
  (\ e -> [d|

  instance 
    (CanPow b $e)
    =>
    CanPow (WithCurrentPrec b p) $e 
    where
    type PowType (WithCurrentPrec b p) $e = WithCurrentPrec (PowType b $e) p
    pow = lift1T pow

  |]))

$(declForTypes
  [[t| Integer |], [t| Int |], [t| Rational |]]
  (\ b -> [d|

  instance 
    (CanPow $b e, HasOrderCertainly e Integer, CanTestInteger e)
    =>
    CanPow $b (WithCurrentPrec e p) 
    where
    type PowType $b (WithCurrentPrec e p) = WithCurrentPrec (PowType $b e) p
    pow = liftT1 pow
  |]))

_example1 :: CN MPBall
_example1 :: CN MPBall
_example1 = Precision
-> (forall (n :: Nat). KnownNat n => WithCurrentPrec (CN MPBall) n)
-> CN MPBall
forall t.
Precision
-> (forall (n :: Nat). KnownNat n => WithCurrentPrec t n) -> t
runWithPrec (Integer -> Precision
prec Integer
1000) forall (n :: Nat). KnownNat n => WithCurrentPrec (CN MPBall) n
piCP

_example2 :: CN MPBall
_example2 :: CN MPBall
_example2 = Precision
-> (forall (n :: Nat). KnownNat n => WithCurrentPrec (CN MPBall) n)
-> CN MPBall
forall t.
Precision
-> (forall (n :: Nat). KnownNat n => WithCurrentPrec t n) -> t
runWithPrec (Integer -> Precision
prec Integer
1000) ((forall (n :: Nat). KnownNat n => WithCurrentPrec (CN MPBall) n)
 -> CN MPBall)
-> (forall (n :: Nat). KnownNat n => WithCurrentPrec (CN MPBall) n)
-> CN MPBall
forall a b. (a -> b) -> a -> b
$ WithCurrentPrec (CN MPBall) n
forall (n :: Nat). KnownNat n => WithCurrentPrec (CN MPBall) n
piCP WithCurrentPrec (CN MPBall) n
-> WithCurrentPrec (CN MPBall) n
-> SubType
     (WithCurrentPrec (CN MPBall) n) (WithCurrentPrec (CN MPBall) n)
forall t1 t2. CanSub t1 t2 => t1 -> t2 -> SubType t1 t2
- WithCurrentPrec (CN MPBall) n
forall (n :: Nat). KnownNat n => WithCurrentPrec (CN MPBall) n
piCP

_example3 :: CN MPBall
_example3 :: CN MPBall
_example3 = Precision
-> (forall (n :: Nat). KnownNat n => WithCurrentPrec (CN MPBall) n)
-> CN MPBall
forall t.
Precision
-> (forall (n :: Nat). KnownNat n => WithCurrentPrec t n) -> t
runWithPrec (Integer -> Precision
prec Integer
1000) ((forall (n :: Nat). KnownNat n => WithCurrentPrec (CN MPBall) n)
 -> CN MPBall)
-> (forall (n :: Nat). KnownNat n => WithCurrentPrec (CN MPBall) n)
-> CN MPBall
forall a b. (a -> b) -> a -> b
$ WithCurrentPrec (CN MPBall) n
-> SqrtType (WithCurrentPrec (CN MPBall) n)
forall t. CanSqrt t => t -> SqrtType t
sqrt (Integer -> WithCurrentPrec (CN MPBall) n
forall t (p :: Nat).
(CanBeMPBallP t, KnownNat p) =>
t -> WithCurrentPrec (CN MPBall) p
mpBallCP Integer
2)