A cli database for some FFX stuff
{-# LANGUAGE DeriveGeneric     #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell   #-}

module AlBhed
    ( -- * Classes
      Primer (..)
    , Volume (..)
      -- * Conversions
    , fromVolume
    , toRoman
    , toVolume
      -- * Lenses
    , alBhed
    , english
    , volume
    ) where

import           Data.List
import           Data.Maybe      (fromJust)

import           Data.Aeson
import qualified Data.Text       as T

import           Control.Lens
import           Control.Lens.TH

import           GHC.Generics

data Volume
    = One
    | Two
    | Three
    | Four
    | Five
    | Six
    | Seven
    | Eight
    | Nine
    | Ten
    | Eleven
    | Twelve
    | Thirteen
    | Fourteen
    | Fifteen
    | Sixteen
    | Seventeen
    | Eigthteen
    | Nineteen
    | Twenty
    | TwentyOne
    | TwentyTwo
    | TwentyThree
    | TwentyFour
    | TwentyFive
    | TwentySix
    deriving (Eq, Ord, Enum, Bounded, Show)

data Primer = Primer
    { _volume  :: Volume
    , _english :: Char
    , _alBhed  :: Char
    }
    deriving (Generic, Show, Eq)

$(makeLenses ''Primer)

toVolume :: Int -> Maybe Volume
toVolume x
    | x >= 1 && x <= 26 = Just $ toEnum (x - 1)
    | otherwise = Nothing

fromVolume :: Volume -> Int
fromVolume = (+1) . fromEnum

toRoman :: Volume -> T.Text
toRoman = go . fromVolume
  where
    go 0 = T.empty
    go x =
        let (break, roman) = fromJust $ findClosestRoman x
        in T.append roman $ go (x - break)

romanSymbols :: [(Int, T.Text)]
romanSymbols =
    [ (10, "X")
    , (9, "IX")
    , (5, "V")
    , (4, "IV")
    , (1, "I")
    ]

findClosestRoman :: Int -> Maybe (Int, T.Text)
findClosestRoman x = find ((x >=) . fst) romanSymbols