{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -fno-warn-redundant-constraints #-}
module Bookkeeper.Internal where
import GHC.OverloadedLabels
import GHC.Generics
import qualified Data.Type.Map as Map
import GHC.TypeLits (Symbol, KnownSymbol, TypeError, ErrorMessage(..))
import Data.Default.Class (Default(..))
import Data.Kind (Type)
import Data.Type.Map (Map, Mapping((:->)))
import Data.Monoid ((<>))
import Data.List (intercalate)
import Bookkeeper.Internal.Errors
type Book a = Book' (Map.AsMap a)
newtype Book' (a :: [Mapping Symbol Type]) = Book { getBook :: Map a }
instance ShowHelper (Book' a) => Show (Book' a) where
  show x = "Book {" <> intercalate ", " (go <$> showHelper x) <> "}"
    where
      go (k, v) = k <> " = " <> v
class ShowHelper a where
  showHelper :: a -> [(String, String)]
instance ShowHelper (Book' '[]) where
  showHelper _ = []
instance ( ShowHelper (Book' xs)
         , KnownSymbol k
         , Show v
         ) => ShowHelper (Book' ((k :=> v) ': xs)) where
  showHelper (Book (Map.Ext k v rest)) = (show k, show v):showHelper (Book rest)
instance Eq (Book' '[]) where
  _ == _ = True
instance (Eq val, Eq (Book' xs)) => Eq (Book' ((field :=> val) ': xs)  ) where
  Book (Map.Ext _ a as) == Book (Map.Ext _ b bs) = a == b && Book as == Book bs
instance Monoid (Book' '[]) where
  mempty = emptyBook
  _ `mappend` _ = emptyBook
instance Default (Book' '[]) where
  def = emptyBook
instance ( Default (Book' xs)
         , Default v
         ) => Default (Book' ((k :=> v) ': xs)) where
  def = Book (Map.Ext Map.Var def (getBook def))
emptyBook :: Book '[]
emptyBook = Book Map.Empty
type a :=> b = a ':-> b
instance (s ~ s') => IsLabel s (Key s') where
#if MIN_VERSION_base(4,10,0)
  fromLabel = Key
#else
  fromLabel _ = Key
#endif
data Key (a :: Symbol) = Key
  deriving (Eq, Show, Read, Generic)
type Gettable field book val = (Map.Submap '[field :=> val] book, Contains book field val)
get :: forall field book val. (Gettable field book val)
  => Key field -> Book' book -> val
get _ (Book bk) = case (Map.submap bk :: Map '[field :=> val]) of
        Map.Ext _ v Map.Empty -> v
(?:) :: forall field book val. (Gettable field book val)
  => Book' book -> Key field -> val
(?:) = flip get
infixl 3 ?:
type Settable field val old new =
  (
    Map.Submap (Map.AsMap (old Map.:\ field)) old
  , Map.Unionable '[ field :=> val] (Map.AsMap (old Map.:\ field))
  , new ~ Map.AsMap (( field :=> val) ': (Map.AsMap (old Map.:\ field)))
  )
set :: forall field val old new .  ( Settable field val old new)
  => Key field -> val -> Book' old -> Book' new
set p v old = Book new
  where
    Book deleted = delete p old
    added = Map.Ext (Map.Var :: Map.Var field) v deleted
    new = Map.asMap added
(=:) :: ( Settable field val old new)
  => Key field -> val -> Book' old -> Book' new
(=:) = set
infix 3 =:
type Modifiable field val val' old new =
  ( Settable field val' old new
  , Map.AsMap new ~ new
  , Contains old field val
  , Map.Submap '[ field :=> val] old
  )
modify :: ( Modifiable field val val' old new)
  =>  Key field -> (val -> val') -> Book' old -> Book new
modify p f b = set p v b
  where v = f $ get p b
(%:) :: ( Modifiable field val val' old new)
  => Key field -> (val -> val') -> Book' old -> Book new
(%:) = modify
infixr 3 %:
delete :: forall field old .
        ( Map.Submap (Map.AsMap (old Map.:\ field)) old
        ) => Key field -> Book' old -> Book (old Map.:\ field)
delete _ (Book bk) = Book $ Map.submap bk
class FromGeneric a book | a -> book where
  fromGeneric :: a x -> Book' book
instance FromGeneric cs book => FromGeneric (D1 m cs) book where
  fromGeneric (M1 xs) = fromGeneric xs
instance FromGeneric cs book => FromGeneric (C1 m cs) book where
  fromGeneric (M1 xs) = fromGeneric xs
instance (v ~ Map.AsMap ('[name ':-> t]))
  => FromGeneric (S1 ('MetaSel ('Just name) p s l) (Rec0 t)) v where
  fromGeneric (M1 (K1 t)) = (Key =: t) emptyBook
instance
  ( FromGeneric l lbook
  , FromGeneric r rbook
  , Map.Unionable lbook rbook
  , book ~ Map.Union lbook rbook
  ) => FromGeneric (l :*: r) book where
  fromGeneric (l :*: r)
    = Book $ Map.union (getBook (fromGeneric l)) (getBook (fromGeneric r))
type family Expected a where
  Expected (l :+: r) = TypeError ('Text "Cannot convert sum types into Books")
  Expected U1        = TypeError ('Text "Cannot convert non-record types into Books")
instance (book ~ Expected (l :+: r)) => FromGeneric (l :+: r) book where
  fromGeneric = error "impossible"
instance {-# OVERLAPPABLE #-}
  (book ~ Expected lhs, lhs ~ U1
  ) => FromGeneric lhs book where
  fromGeneric = error "impossible"
fromRecord :: (Generic a, FromGeneric (Rep a) bookRep) => a -> Book' bookRep
fromRecord = fromGeneric . from