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

module AlBhed.Index
    ( -- * Types
      AlBhedIndex
    , IndexItem (..)
      -- * Constructors
    , empty
    , singleton
      -- * Accessors
    , getPrimer
      -- * Modify
    , addLocation
      -- * Converting
    , oneline
    , toDoc
      -- * Prisms
    , _IndexItem
    ) where

import           Control.Lens
import           Control.Lens.TH

import           Data.Text          (Text)
import qualified Data.Text          as T
import           Prettyprinter

import           Data.IntMap        (IntMap)
import qualified Data.IntMap        as IMap

import           Data.NonEmptyList  (NonEmptyList)
import qualified Data.NonEmptyList  as NonEmptyList

import           AlBhed
import qualified Data.PrintableText as PrintableText
import           Location

type AlBhedIndex = IntMap IndexItem
newtype IndexItem = IndexItem (Primer, NonEmptyList Location) deriving (Show)

$(makePrisms ''IndexItem)

empty :: AlBhedIndex
empty = IMap.empty

singleton :: Primer -> Location -> AlBhedIndex
singleton x y = IMap.singleton (x ^. volume & fromVolume) (IndexItem (x, NonEmptyList.singleton y))

-- | Add a location to the primer in index
-- | If the primer is not in the index then we add the primer and location to the index
-- | Case 1: Primer volume is not in the Index, insert it as a new node
-- | Case 2: Primer exist so append location to primer locations
addLocation :: Primer -> Location -> AlBhedIndex -> AlBhedIndex
addLocation primer location map =
    let vol = fromVolume $ primer ^. volume
        f (IndexItem (p, ls)) (IndexItem (_, ls')) = IndexItem (p, NonEmptyList.merge ls ls')
        in IMap.insertWith f vol (IndexItem (primer, NonEmptyList.singleton location)) map

-- | Get the primer from an index or Nothing if not found
getPrimer :: Volume -> AlBhedIndex -> Maybe Primer
getPrimer vol index = index ^? traverse . _IndexItem . _1 . filtered (\(Primer vol' _ _) -> vol' == vol)

oneline :: Doc () -> Doc ()
oneline = group

-- | Convert an AlBhed Index database to a prettyprinter `Doc` type
toDoc :: (Doc () -> Doc ()) -> AlBhedIndex -> Doc ()
toDoc mod = vsep . map (mod . indexItemToDoc) . IMap.elems
    where
        indexItemToDoc :: IndexItem -> Doc ()
        indexItemToDoc (IndexItem (primer, locations)) =
            flatAlt
                (primerToDoc primer <> line
                <> align (indent 2 . vsep $ locationToDoc <$> NonEmptyList.toList locations))
                (primerToDoc primer <> softline
                <> list (locationToDoc <$> NonEmptyList.toList locations))
        primerToDoc :: Primer -> Doc ()
        primerToDoc primer =
            "Primer" <+> pretty (toRoman $ primer ^. volume) <+> squotes (pretty $ primer ^. alBhed)
            <+> "->" <+> squotes (pretty $ primer ^. english)
        locationToDoc :: Location -> Doc ()
        locationToDoc loc = (pretty . PrintableText.unPrintableText $ loc ^. area)
            <> maybe emptyDoc ((" -" <+>) . pretty . PrintableText.unPrintableText) (loc ^. section)