{-# LANGUAGE CPP, Safe #-}

{-|
Module      : Data.Char.Small
Description : A module used to render subscript and superscript in Unicode.
Maintainer  : hapytexeu+gh@gmail.com
Stability   : experimental
Portability : POSIX

One can make use of a <https://www.unicode.org/charts/PDF/U2070.pdf block of Unicode characters> to /emulate/ subscript and superscript. Note that the subscript and superscript will be
aligned with the /baseline/ and the /cap line/ respectively, and is thus not equivalent to @<sub>...</sub>@ and @<sup>...</sup>@ in HTML. Furthermore only a small subset of characters
is supported.

This module allows one to map certain characters to their subscript and superscript counterpart, and furthermore makes it more convenient to transform a number (both positive and negative)
to a 'Text' that specifies this number in subscript and superscript.
-}

module Data.Char.Small (
  -- * Convert characters to their subscript and superscript counterpart
    toSub, toSup
  -- * Convert superscript and subscript back their normal character
  , fromSubSup
  -- * Numbers as subscript and superscript.
  , asSub, asSub', asSubPlus
  , asSup, asSup', asSupPlus
  -- * Ratio formatting
  , ratioToUnicode, ratioToUnicode', ratioPartsToUnicode, ratioPartsToUnicode'
  -- * Ratio parsing
  , unicodeToRatio, unicodeToRatioParts
  ) where

import Data.Bits((.&.), (.|.))
import Data.Char(chr, isDigit, ord)
import Data.Char.Core(PlusStyle(WithPlus, WithoutPlus), positionalNumberSystem10)
import Data.Default(Default(def))
import Data.Ratio(Ratio, denominator, numerator, (%))
#if __GLASGOW_HASKELL__ < 803
import Data.Semigroup((<>))
#endif

import qualified Data.Text as T
import Data.Text(Text, cons, snoc, singleton, unpack)

import Text.Read(readMaybe)

-- | Convert a set of characters to their superscript counterpart, given that
-- characters exists.
toSup
    :: Char  -- ^ The given character to convert to its superscript counterpart.
    -> Maybe Char  -- ^ A character wrapped in a 'Just' given the counterpart exists, 'Nothing' otherwise.
toSup :: Char -> Maybe Char
toSup Char
'i' = forall a. a -> Maybe a
Just Char
'\x2071'
toSup Char
'+' = forall a. a -> Maybe a
Just Char
'\x207a'
toSup Char
'-' = forall a. a -> Maybe a
Just Char
'\x207b'
toSup Char
'\x2212' = forall a. a -> Maybe a
Just Char
'\x207b'
toSup Char
'=' = forall a. a -> Maybe a
Just Char
'\x207c'
toSup Char
'(' = forall a. a -> Maybe a
Just Char
'\x207d'
toSup Char
')' = forall a. a -> Maybe a
Just Char
'\x207e'
toSup Char
'n' = forall a. a -> Maybe a
Just Char
'\x207f'
toSup Char
c | Char -> Bool
isDigit Char
c = forall a. a -> Maybe a
Just (Int -> Char
_digitToSub (Char -> Int
ord Char
c forall a. Num a => a -> a -> a
- Char -> Int
ord Char
'0'))
        | Bool
otherwise = forall a. Maybe a
Nothing

-- | Convert a set of characters to their subscript counterpart, given that
-- characters exists.
toSub
    :: Char  -- ^ The given character to convert to its subscript counterpart.
    -> Maybe Char  -- ^ A character wrapped in a 'Just' given the counterpart exists, 'Nothing' otherwise.
toSub :: Char -> Maybe Char
toSub Char
'+' = forall a. a -> Maybe a
Just Char
'\x208a'
toSub Char
'-' = forall a. a -> Maybe a
Just Char
'\x208b'
toSub Char
'\x2212' = forall a. a -> Maybe a
Just Char
'\x208b'
toSub Char
'=' = forall a. a -> Maybe a
Just Char
'\x208c'
toSub Char
'(' = forall a. a -> Maybe a
Just Char
'\x208d'
toSub Char
')' = forall a. a -> Maybe a
Just Char
'\x208e'
toSub Char
'a' = forall a. a -> Maybe a
Just Char
'\x2090'
toSub Char
'e' = forall a. a -> Maybe a
Just Char
'\x2091'
toSub Char
'o' = forall a. a -> Maybe a
Just Char
'\x2092'
toSub Char
'x' = forall a. a -> Maybe a
Just Char
'\x2093'
toSub Char
'\x259' = forall a. a -> Maybe a
Just Char
'\x2094'
toSub Char
'h' = forall a. a -> Maybe a
Just Char
'\x2095'
toSub Char
'k' = forall a. a -> Maybe a
Just Char
'\x2096'
toSub Char
'l' = forall a. a -> Maybe a
Just Char
'\x2097'
toSub Char
'm' = forall a. a -> Maybe a
Just Char
'\x2098'
toSub Char
'n' = forall a. a -> Maybe a
Just Char
'\x2099'
toSub Char
'p' = forall a. a -> Maybe a
Just Char
'\x209a'
toSub Char
's' = forall a. a -> Maybe a
Just Char
'\x209b'
toSub Char
't' = forall a. a -> Maybe a
Just Char
'\x209c'
toSub Char
c | Char -> Bool
isDigit Char
c = forall a. a -> Maybe a
Just (Int -> Char
_digitToSub (Char -> Int
ord Char
c forall a. Num a => a -> a -> a
- Char -> Int
ord Char
'0'))
        | Bool
otherwise = forall a. Maybe a
Nothing

_fromSubSup :: Int -> Char
_fromSubSup :: Int -> Char
_fromSubSup Int
0xa = Char
'+'
_fromSubSup Int
0xb = Char
'-'
_fromSubSup Int
0xc = Char
'='
_fromSubSup Int
0xd = Char
'('
_fromSubSup Int
0xe = Char
')'
_fromSubSup Int
_ = forall a. HasCallStack => [Char] -> a
error [Char]
"Should not happen!"

-- | Convert subscripts and superscripts back to the original counterpart, so @'⁵'@ back to @'5'@. For non-subscript or -superscript
-- characters, it returns the original character.
fromSubSup
  :: Char  -- ^ A character to un-subscript or un-superscript, for example @'⁵'@.
  -> Char  -- ^ The corresponding original character, for example @'5'@.
fromSubSup :: Char -> Char
fromSubSup Char
'\x2070' = Char
'0'
fromSubSup Char
'\xb2' = Char
'2'
fromSubSup Char
'\xb3' = Char
'3'
fromSubSup Char
'\xb9' = Char
'1'
fromSubSup Char
'\x2071' = Char
'i'
fromSubSup Char
'\x207f' = Char
'n'
fromSubSup Char
'\x2090' = Char
'a'
fromSubSup Char
'\x2091' = Char
'e'
fromSubSup Char
'\x2092' = Char
'o'
fromSubSup Char
'\x2093' = Char
'x'
fromSubSup Char
'\x2094' = Char
'\x259'
fromSubSup Char
'\x2095' = Char
'h'
fromSubSup Char
'\x2096' = Char
'k'
fromSubSup Char
'\x2097' = Char
'l'
fromSubSup Char
'\x2098' = Char
'm'
fromSubSup Char
'\x2099' = Char
'n'
fromSubSup Char
'\x209a' = Char
'p'
fromSubSup Char
'\x209b' = Char
's'
fromSubSup Char
'\x209c' = Char
't'
fromSubSup Char
x
  | Char
'\x207a' forall a. Ord a => a -> a -> Bool
<= Char
x Bool -> Bool -> Bool
&& Char
xforall a. Ord a => a -> a -> Bool
<= Char
'\x208e' Bool -> Bool -> Bool
&& Int
0x0a forall a. Ord a => a -> a -> Bool
<= Int
m Bool -> Bool -> Bool
&& Int
m forall a. Ord a => a -> a -> Bool
<= Int
0x0e = Int -> Char
_fromSubSup Int
m
  | Char
'\x2074' forall a. Ord a => a -> a -> Bool
<= Char
x Bool -> Bool -> Bool
&& Char
x forall a. Ord a => a -> a -> Bool
<= Char
'\x2089' = Int -> Char
chr (Int
0x30 forall a. Bits a => a -> a -> a
.|. (Char -> Int
ord Char
x forall a. Bits a => a -> a -> a
.&. Int
0xf))
  | Bool
otherwise = Char
x
  where m :: Int
m = Char -> Int
ord Char
x forall a. Bits a => a -> a -> a
.&. Int
0xf

_value :: Integral i => (Int -> Char) -> i -> Text
_value :: forall i. Integral i => (Int -> Char) -> i -> Text
_value Int -> Char
f = i -> Text
go
    where f' :: i -> Char
f' = Int -> Char
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral
          go :: i -> Text
go i
n | i
n forall a. Ord a => a -> a -> Bool
<= i
9 = Char -> Text
singleton (i -> Char
f' i
n)
               | Bool
otherwise = Text -> Char -> Text
snoc (i -> Text
go i
q) (i -> Char
f' i
r)
               where (i
q,i
r) = forall a. Integral a => a -> a -> (a, a)
quotRem i
n i
10

_prefixSign :: Integral i => Char -> (Int -> Char) -> i -> Text
_prefixSign :: forall i. Integral i => Char -> (Int -> Char) -> i -> Text
_prefixSign Char
c Int -> Char
f i
v
  | i
v forall a. Ord a => a -> a -> Bool
< i
0 = Char -> Text -> Text
cons Char
c (i -> Text
f' (-i
v))
  | Bool
otherwise = i -> Text
f' i
v
  where f' :: i -> Text
f' = forall i. Integral i => (Int -> Char) -> i -> Text
_value Int -> Char
f

_prefixSignPlus :: Integral i => Char -> Char -> (Int -> Char) -> i -> Text
_prefixSignPlus :: forall i. Integral i => Char -> Char -> (Int -> Char) -> i -> Text
_prefixSignPlus Char
cp Char
cn Int -> Char
f i
v
  | i
v forall a. Ord a => a -> a -> Bool
< i
0 = Char -> i -> Text
c' Char
cn (-i
v)
  | Bool
otherwise = Char -> i -> Text
c' Char
cp i
v
  where c' :: Char -> i -> Text
c' = (forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall i. Integral i => (Int -> Char) -> i -> Text
_value Int -> Char
f) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Text -> Text
cons

-- | Converting the given numerator and denominator to a fraction
-- where the numerator is written in superscript, and the denominator
-- in subscript. If the denominator is negative, the item is rendered
-- with a minus at the numerator part.
ratioPartsToUnicode :: (Integral i, Integral j)
  => PlusStyle -- ^ the given plus style that will be applied to the numerator.
  -> i  -- ^ The given numerator.
  -> j  -- ^ The given denominator.
  -> Text  -- ^ A 'Text' object that presents the fraction with superscript and subscript.
ratioPartsToUnicode :: forall i j. (Integral i, Integral j) => PlusStyle -> i -> j -> Text
ratioPartsToUnicode PlusStyle
ps i
num j
den
  | j
den forall a. Ord a => a -> a -> Bool
< j
0 = forall i j. (Integral i, Integral j) => PlusStyle -> i -> j -> Text
ratioPartsToUnicode PlusStyle
ps (-i
num) (-j
den)
  | Bool
otherwise = forall i. Integral i => PlusStyle -> i -> Text
asSup PlusStyle
ps i
num forall a. Semigroup a => a -> a -> a
<> Char -> Text -> Text
cons Char
'\x2044' (forall i. Integral i => i -> Text
asSub' j
den)

-- | Converting the given numerator and denominator to a fraction
-- where the numerator is written in superscript, and the denominator
-- in subscript. If the denominator is negative, the item is rendered
-- with a minus at the numerator part.
ratioPartsToUnicode' :: (Integral i, Integral j)
  => i  -- ^ The given numerator.
  -> j  -- ^ The given denominator.
  -> Text  -- ^ A 'Text' object that presents the fraction with superscript and subscript.
ratioPartsToUnicode' :: forall i j. (Integral i, Integral j) => i -> j -> Text
ratioPartsToUnicode' = forall i j. (Integral i, Integral j) => PlusStyle -> i -> j -> Text
ratioPartsToUnicode forall a. Default a => a
def

-- | Try to convert the given text that contains a fraction to the numerator and denominator. This does *not* take /vulgar fractions/
-- into account. You can process these with 'Dat.Char.Number.VulgarFraction.fromVulgarFallback'.
unicodeToRatioParts :: (Read i, Read j)
  => Text  -- ^ The 'Text' we try to decode.
  -> Maybe (i, j)  -- ^ A 2-tuple with the numerator and denominator wrapped in a 'Just' if the fraction can be parsed, 'Nothing' otherwise.
unicodeToRatioParts :: forall i j. (Read i, Read j) => Text -> Maybe (i, j)
unicodeToRatioParts Text
t = (,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall i. Read i => [Char] -> Maybe i
_parseInt (Text -> [Char]
unpack Text
n) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall i. Read i => [Char] -> Maybe i
_parseInt (forall a. Int -> [a] -> [a]
drop Int
1 (Text -> [Char]
unpack Text
d))
  where ~(Text
n, Text
d) = (Char -> Bool) -> Text -> (Text, Text)
T.break Char -> Bool
_isFrac ((Char -> Char) -> Text -> Text
T.map Char -> Char
fromSubSup Text
t)

-- | Try to convert the given text that contains a fraction to a 'Ratio'. This does *not* take /vulgar fractions/
-- into account. You can process these with 'Dat.Char.Number.VulgarFraction.fromVulgarFallbackToRatio'.
unicodeToRatio :: (Integral i, Read i)
  => Text  -- ^ The 'Text' we try to decode.
  -> Maybe (Ratio i)  -- ^ The fraction wrapped in a 'Just'; 'Nothing' if the fraction can not be parsed.
unicodeToRatio :: forall i. (Integral i, Read i) => Text -> Maybe (Ratio i)
unicodeToRatio = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry forall a. Integral a => a -> a -> Ratio a
(%)) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall i j. (Read i, Read j) => Text -> Maybe (i, j)
unicodeToRatioParts

-- | Convert the given 'Ratio' object to a sequence of characters with the
-- numerator in superscript and the denominator in subscript. The given
-- 'PlusStyle' is applied to the numerator.
ratioToUnicode :: Integral i
  => PlusStyle  -- ^ The given 'PlusStyle' to use.
  -> Ratio i  -- ^ The given 'Ratio' object to convert to a 'Text'.
  -> Text  -- ^ A 'Text' object that denotes the given 'Ratio' making use of superscript and subscript.
ratioToUnicode :: forall i. Integral i => PlusStyle -> Ratio i -> Text
ratioToUnicode PlusStyle
ps Ratio i
dn = forall i j. (Integral i, Integral j) => PlusStyle -> i -> j -> Text
ratioPartsToUnicode PlusStyle
ps (forall a. Ratio a -> a
numerator Ratio i
dn) (forall a. Ratio a -> a
denominator Ratio i
dn)

-- | Format a given 'Ratio' object to a 'Text' value that formats the ratio with
-- superscript and subscript using the 'Default' 'PlusStyle'.
ratioToUnicode' :: Integral i
    => Ratio i  -- ^ The given 'Ratio' value to format.
    -> Text  -- ^ The 'Text' block that contains a textual representation of the 'Ratio'.
ratioToUnicode' :: forall i. Integral i => Ratio i -> Text
ratioToUnicode' = forall i. Integral i => PlusStyle -> Ratio i -> Text
ratioToUnicode forall a. Default a => a
def

-- | Convert a number (positive or negative) to a 'Text' object that denotes
-- that number in superscript characters.
asSup :: Integral i
  => PlusStyle  -- ^ The given 'PlusStyle' to use.
  -> i  -- ^ The given number to convert.
  -> Text  -- ^ A 'Text' value that denotes the number as a sequence of superscript characters.
asSup :: forall i. Integral i => PlusStyle -> i -> Text
asSup = forall i.
Integral i =>
(Int -> Char) -> Char -> Char -> PlusStyle -> i -> Text
positionalNumberSystem10 Int -> Char
_digitToSup Char
'\x207a' Char
'\x207b'

-- | Convert a number (positive or negative) to a 'Text' object that denotes that
-- number in superscript characters.
asSup' :: Integral i
    => i  -- ^ The number to convert.
    -> Text  -- ^ A 'Text' value that contains the number as a sequence of superscript characters.
asSup' :: forall i. Integral i => i -> Text
asSup' = forall i. Integral i => PlusStyle -> i -> Text
asSup PlusStyle
WithoutPlus

-- | Convert a number (positive or negative) to a 'Text' that specifies that
-- number in superscript characters. For positive characters, the superscript
-- contains a plus character (@⁺@).
asSupPlus :: Integral i
    => i  -- ^ The number to convert.
    -> Text  -- ^ A 'Text' value that contains the number as a sequence of superscript characters.
asSupPlus :: forall i. Integral i => i -> Text
asSupPlus = forall i. Integral i => PlusStyle -> i -> Text
asSup PlusStyle
WithPlus -- _prefixSignPlus '\x207a' '\x207b' _digitToSup

-- | Convert a number (positive or negative) to a 'Text' object that denotes
-- that number in subscript characters.
asSub :: Integral i
  => PlusStyle  -- ^ The given 'PlusStyle' to use.
  -> i  -- ^ The given number to convert.
  -> Text  -- ^ A 'Text' value that denotes the number as a sequence of subscript characters.
asSub :: forall i. Integral i => PlusStyle -> i -> Text
asSub = forall i.
Integral i =>
(Int -> Char) -> Char -> Char -> PlusStyle -> i -> Text
positionalNumberSystem10 Int -> Char
_digitToSub Char
'\x208a' Char
'\x208b'

-- | Convert a number (positive or negative) to a 'Text' that specifies that
-- number in subscript characters.
asSub' :: Integral i
    => i  -- ^ The number to convert.
    -> Text  -- ^ A 'Text' value that contains the number as a sequence of subscript characters.
asSub' :: forall i. Integral i => i -> Text
asSub' = forall i. Integral i => PlusStyle -> i -> Text
asSub PlusStyle
WithoutPlus

-- | Convert a number (positive or negative) to a 'Text' that specifies that
-- number in subscript characters. For positive characters, the subscript
-- contains a plus character (@₊@).
asSubPlus :: Integral i
    => i  -- ^ The number to convert.
    -> Text  -- ^ A 'Text' value that contains the number as a sequence of subscript characters.
asSubPlus :: forall i. Integral i => i -> Text
asSubPlus = forall i. Integral i => PlusStyle -> i -> Text
asSub PlusStyle
WithPlus

_digitToSub :: Int -> Char
_digitToSub :: Int -> Char
_digitToSub = Int -> Char
chr forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int
8320forall a. Num a => a -> a -> a
+)

_digitToSup :: Int -> Char
_digitToSup :: Int -> Char
_digitToSup Int
0 = Char
'\x2070'
_digitToSup Int
1 = Char
'\xb9'
_digitToSup Int
n | Int
n forall a. Ord a => a -> a -> Bool
<= Int
3 = Int -> Char
chr (Int
176forall a. Num a => a -> a -> a
+Int
n)
              | Bool
otherwise = Int -> Char
chr (Int
8304forall a. Num a => a -> a -> a
+Int
n)

_parseInt :: Read i => String -> Maybe i
_parseInt :: forall i. Read i => [Char] -> Maybe i
_parseInt (Char
'+':[Char]
d) = forall i. Read i => [Char] -> Maybe i
readMaybe [Char]
d
_parseInt [Char]
d = forall i. Read i => [Char] -> Maybe i
readMaybe [Char]
d

_isFrac :: Char -> Bool
_isFrac :: Char -> Bool
_isFrac Char
'/' = Bool
True
_isFrac Char
'\x2044' = Bool
True
_isFrac Char
_ = Bool
False