{-# LANGUAGE 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
  -- * Numbers as subscript and superscript.
  , asSub, asSub', asSubPlus
  , asSup, asSup', asSupPlus
  -- * Ratio formatting
  , ratioToUnicode, ratioToUnicode'
  ) where

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)
import Data.Text(Text, cons, snoc, singleton)

-- | 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' = Char -> Maybe Char
forall a. a -> Maybe a
Just Char
'\x2071'
toSup Char
'+' = Char -> Maybe Char
forall a. a -> Maybe a
Just Char
'\x207a'
toSup Char
'-' = Char -> Maybe Char
forall a. a -> Maybe a
Just Char
'\x207b'
toSup Char
'\x2212' = Char -> Maybe Char
forall a. a -> Maybe a
Just Char
'\x207b'
toSup Char
'=' = Char -> Maybe Char
forall a. a -> Maybe a
Just Char
'\x207c'
toSup Char
'(' = Char -> Maybe Char
forall a. a -> Maybe a
Just Char
'\x207d'
toSup Char
')' = Char -> Maybe Char
forall a. a -> Maybe a
Just Char
'\x207e'
toSup Char
'n' = Char -> Maybe Char
forall a. a -> Maybe a
Just Char
'\x207f'
toSup Char
c | Char -> Bool
isDigit Char
c = Char -> Maybe Char
forall a. a -> Maybe a
Just (Int -> Char
_digitToSub (Char -> Int
ord Char
c Int -> Int -> Int
forall a. Num a => a -> a -> a
- Char -> Int
ord Char
'0'))
        | Bool
otherwise = Maybe Char
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
'+' = Char -> Maybe Char
forall a. a -> Maybe a
Just Char
'\x208a'
toSub Char
'-' = Char -> Maybe Char
forall a. a -> Maybe a
Just Char
'\x208b'
toSub Char
'\x2212' = Char -> Maybe Char
forall a. a -> Maybe a
Just Char
'\x208b'
toSub Char
'=' = Char -> Maybe Char
forall a. a -> Maybe a
Just Char
'\x208c'
toSub Char
'(' = Char -> Maybe Char
forall a. a -> Maybe a
Just Char
'\x208d'
toSub Char
')' = Char -> Maybe Char
forall a. a -> Maybe a
Just Char
'\x208e'
toSub Char
'a' = Char -> Maybe Char
forall a. a -> Maybe a
Just Char
'\x2090'
toSub Char
'e' = Char -> Maybe Char
forall a. a -> Maybe a
Just Char
'\x2091'
toSub Char
'o' = Char -> Maybe Char
forall a. a -> Maybe a
Just Char
'\x2092'
toSub Char
'x' = Char -> Maybe Char
forall a. a -> Maybe a
Just Char
'\x2093'
toSub Char
'\x259' = Char -> Maybe Char
forall a. a -> Maybe a
Just Char
'\x2094'
toSub Char
'h' = Char -> Maybe Char
forall a. a -> Maybe a
Just Char
'\x2095'
toSub Char
'k' = Char -> Maybe Char
forall a. a -> Maybe a
Just Char
'\x2095'
toSub Char
'l' = Char -> Maybe Char
forall a. a -> Maybe a
Just Char
'\x2095'
toSub Char
'm' = Char -> Maybe Char
forall a. a -> Maybe a
Just Char
'\x2095'
toSub Char
'n' = Char -> Maybe Char
forall a. a -> Maybe a
Just Char
'\x2095'
toSub Char
'p' = Char -> Maybe Char
forall a. a -> Maybe a
Just Char
'\x2095'
toSub Char
's' = Char -> Maybe Char
forall a. a -> Maybe a
Just Char
'\x2095'
toSub Char
't' = Char -> Maybe Char
forall a. a -> Maybe a
Just Char
'\x2095'
toSub Char
c | Char -> Bool
isDigit Char
c = Char -> Maybe Char
forall a. a -> Maybe a
Just (Int -> Char
_digitToSub (Char -> Int
ord Char
c Int -> Int -> Int
forall a. Num a => a -> a -> a
- Char -> Int
ord Char
'0'))
        | Bool
otherwise = Maybe Char
forall a. Maybe a
Nothing

_value :: Integral i => (Int -> Char) -> i -> Text
_value :: (Int -> Char) -> i -> Text
_value Int -> Char
f = i -> Text
go
    where f' :: i -> Char
f' = Int -> Char
f (Int -> Char) -> (i -> Int) -> i -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. i -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral
          go :: i -> Text
go i
n | i
n i -> i -> Bool
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) = i -> i -> (i, i)
forall a. Integral a => a -> a -> (a, a)
quotRem i
n i
10

_prefixSign :: Integral i => Char -> (Int -> Char) -> i -> Text
_prefixSign :: Char -> (Int -> Char) -> i -> Text
_prefixSign Char
c Int -> Char
f i
v
  | i
v i -> i -> Bool
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' = (Int -> Char) -> i -> Text
forall i. Integral i => (Int -> Char) -> i -> Text
_value Int -> Char
f

_prefixSignPlus :: Integral i => Char -> Char -> (Int -> Char) -> i -> Text
_prefixSignPlus :: Char -> Char -> (Int -> Char) -> i -> Text
_prefixSignPlus Char
cp Char
cn Int -> Char
f i
v
  | i
v i -> i -> Bool
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' = ((Text -> Text) -> (i -> Text) -> i -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Char) -> i -> Text
forall i. Integral i => (Int -> Char) -> i -> Text
_value Int -> Char
f) ((Text -> Text) -> i -> Text)
-> (Char -> Text -> Text) -> Char -> i -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Text -> Text
cons

-- | 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 :: PlusStyle -> Ratio i -> Text
ratioToUnicode PlusStyle
ps Ratio i
dn = PlusStyle -> i -> Text
forall i. Integral i => PlusStyle -> i -> Text
asSup PlusStyle
ps (Ratio i -> i
forall a. Ratio a -> a
numerator Ratio i
dn) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Char -> Text -> Text
cons Char
'\x2044' (i -> Text
forall i. Integral i => i -> Text
asSub' (Ratio i -> i
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' :: Ratio i -> Text
ratioToUnicode' = PlusStyle -> Ratio i -> Text
forall i. Integral i => PlusStyle -> Ratio i -> Text
ratioToUnicode PlusStyle
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 :: PlusStyle -> i -> Text
asSup = (Int -> Char) -> Char -> Char -> PlusStyle -> i -> Text
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' :: i -> Text
asSup' = PlusStyle -> i -> Text
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 :: i -> Text
asSupPlus = PlusStyle -> i -> Text
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 :: PlusStyle -> i -> Text
asSub = (Int -> Char) -> Char -> Char -> PlusStyle -> i -> Text
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' :: i -> Text
asSub' = PlusStyle -> i -> Text
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 :: i -> Text
asSubPlus = PlusStyle -> i -> Text
forall i. Integral i => PlusStyle -> i -> Text
asSub PlusStyle
WithPlus

_digitToSub :: Int -> Char
_digitToSub :: Int -> Char
_digitToSub = Int -> Char
chr (Int -> Char) -> (Int -> Int) -> Int -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int
8320Int -> Int -> Int
forall 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 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
3 = Int -> Char
chr (Int
176Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
n)
              | Bool
otherwise = Int -> Char
chr (Int
8304Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
n)