module IR where

import Data.List (mapAccumL)
import qualified Data.Map as M

data PrlgStr
  = CallS String [PrlgStr]
  | LiteralS String
  deriving (Show)

data Id =
  Id
    { str :: Int
    , arity :: Int
    }
  deriving (Show, Eq, Ord)

data PrlgInt
  = CallI Id [PrlgInt]
  | LiteralI Int
  | VarI Int Int -- VarI localIndex strTableString
  | VoidI
  deriving (Show)

data StrTable =
  StrTable Int (M.Map String Int) (M.Map Int String)
  deriving (Show)

emptystrtable = StrTable 1 M.empty M.empty

strtablize t@(StrTable nxt fwd rev) str =
  case fwd M.!? str of
    Just i -> (t, i)
    _ -> (StrTable (nxt + 1) (M.insert str nxt fwd) (M.insert nxt str rev), nxt)

internPrlg :: StrTable -> PrlgStr -> (StrTable, PrlgInt)
internPrlg = go
  where
    go t (LiteralS str) = LiteralI <$> strtablize t str
    go t (CallS str ps) =
      let (t', i) = strtablize t str
       in CallI (Id i $ length ps) <$> mapAccumL go t' ps