module Data.Digit.Natural
( _NaturalDigits
, naturalToDigits
, digitsToNatural
) where
import Prelude (Int, error, fromIntegral, maxBound, (*),
(+), (-), (>), (^))
import Control.Category ((.))
import Control.Lens (Prism', ifoldrM, prism', ( # ))
import Data.Foldable (length)
import Data.Function (($))
import Data.Functor (fmap, (<$>))
import Data.Semigroup ((<>))
import Data.List (replicate)
import Data.List.NonEmpty (NonEmpty ((:|)))
import qualified Data.List.NonEmpty as NE
import Data.Maybe (Maybe (..))
import Data.Digit.Decimal
import Data.Digit.Integral (integralDecimal)
import Numeric.Natural (Natural)
import Data.Scientific (toDecimalDigits)
_NaturalDigits :: Prism' (NonEmpty DecDigit) Natural
_NaturalDigits = prism' naturalToDigits digitsToNatural
naturalToDigits :: Natural -> NonEmpty DecDigit
naturalToDigits n =
case toDecimalDigits $ fromIntegral n of
([], _ ) -> error "Data.Scientific.toDecimalDigits is no longer correct!"
(x:xs, eXP) -> g x :| (g <$> xs) <> t (x:xs) eXP
where
t allDigs eXP =
replicate (eXP - length allDigs) (d0 # ())
g 0 = d0 # ()
g 1 = d1 # ()
g 2 = d2 # ()
g 3 = d3 # ()
g 4 = d4 # ()
g 5 = d5 # ()
g 6 = d6 # ()
g 7 = d7 # ()
g 8 = d8 # ()
g 9 = d9 # ()
g _ = error "The universe now has more than ten digits."
digitsToNatural :: NonEmpty DecDigit -> Maybe Natural
digitsToNatural = fmap fromIntegral . ifoldrM f 0 . NE.reverse
where
f :: Int -> DecDigit -> Int -> Maybe Int
f i d curr =
let
next = (integralDecimal # d) * (10 ^ i)
in
if curr > maxBound - next
then Nothing
else Just (curr + next)