{- This file is part of razom-text-util.
 -
 - Written in 2015 by fr33domlover <fr33domlover@rel4tion.org>.
 -
 - ♡ Copying is an act of love. Please copy, reuse and share.
 -
 - The author(s) have dedicated all copyright and related and neighboring
 - rights to this software to the public domain worldwide. This software is
 - distributed without any warranty.
 -
 - You should have received a copy of the CC0 Public Domain Dedication along
 - with this software. If not, see
 - <http://creativecommons.org/publicdomain/zero/1.0/>.
 -}

module Text.Razom.Number
    ( isBinDigit
    , digitsToNum
    , binit
    , octit
    , digit
    , hexit
    , binary
    , octal
    , decimal
    , hexadecimal
    , signed
    , fromDigits
    )
where

import Data.Char (digitToInt, isOctDigit)
import Data.Smaoin (RealNum, realnum)
import Text.Razom.Types
import Text.Regex.Applicative
import Text.Regex.Applicative.Common

-- | Selects ASCII binary digits, i.e. @\'0\'@ and @\'1@\'.
isBinDigit :: Char -> Bool
isBinDigit c = c == '0' || c == '1'

-- | Given the radix and an integer represented as a list of digits, construct
-- a number of the represented value.
--
-- >>> digitsToNum 2 [1, 0, 1, 1, 0, 1]
-- 45
--
-- >>> digitsToNum 16 [15, 15]
-- 255
digitsToNum :: (Num a) => a -> [a] -> a
digitsToNum radix = foldl (\ n i -> n * radix + i) 0

binit :: Num a => Regex a
binit = fromIntegral . digitToInt <$> psym isBinDigit

octit :: Num a => Regex a
octit = fromIntegral . digitToInt <$> psym isOctDigit

hexit = hexDigit

binary :: Num a => Regex a
binary = digitsToNum 2 <$> some binit

octal :: Num a => Regex a
octal = digitsToNum 8 <$> some octit

-- | Read a decimal number string into a 'RealNum' value. The parameters are
-- the digits before the decimal point (integer part) and after it (fraction
-- part). Example with the number 142.857:
--
-- >>> fromDigits [1, 4, 2] [8, 5, 7]
-- RealNum 142857 -3
fromDigits :: [Int] -> [Int] -> RealNum
fromDigits s e = realnum (fromIntegral $ digitsToNum 10 $ s ++ e)
                         (fromIntegral $ negate $ length e)