module Codec.Beam.Internal.Syntax where
import Data.ByteString.Lazy (ByteString)
import Data.Text (Text)
import Data.Word (Word8)
data Op = Op Word8 [Argument]
newtype Label = Label Int
  deriving (Eq, Ord, Show)
newtype X = X Int
  deriving (Eq, Ord, Show)
newtype Y = Y Int
  deriving (Eq, Ord, Show)
newtype F = F Int
  deriving (Eq, Ord, Show)
data Nil = Nil
  deriving (Eq, Ord, Show)
data Lambda = Lambda
  { _lambda_name :: Text   
  , _lambda_arity :: Int
  , _lambda_label :: Label 
  , _lambda_free :: Int    
  }
  deriving (Eq, Ord, Show)
data Literal
  = Integer Int
  | Float Double
  | Atom Text
  | Binary ByteString
  | Tuple [Literal]
  | List [Literal]
  | Map [(Literal, Literal)]
  | ExternalFun Import
  deriving (Eq, Ord, Show)
data Import = Import
  { _import_module :: Text
  , _import_function :: Text
  , _import_arity :: Int
  }
  deriving (Eq, Ord, Show)
class NoGC a
importBif0 :: Bif0 a => a -> Import
importBif0 = unBif 0
class IsBif a => Bif0 a
importBif1 :: Bif1 a => a -> Import
importBif1 = unBif 1
class IsBif a => Bif1 a
importBif2 :: Bif2 a => a -> Import
importBif2 = unBif 2
class IsBif a => Bif2 a
importBif3 :: Bif3 a => a -> Import
importBif3 = unBif 3
class IsBif a => Bif3 a
importBif4 :: Bif4 a => a -> Import
importBif4 = unBif 4
class IsBif a => Bif4 a
newtype  Register  = Register { unRegister :: Argument }
class    IsRegister a        where toRegister :: a -> Register
instance IsRegister Register where toRegister = id
instance IsRegister X        where toRegister = Register . FromX
instance IsRegister Y        where toRegister = Register . FromY
newtype  Source = Source { unSource :: Argument }
class    IsSource a       where toSource :: a -> Source
instance IsSource Source  where toSource = id
instance IsSource X       where toSource = Source . FromX
instance IsSource Y       where toSource = Source . FromY
instance IsSource Nil     where toSource = Source . FromNil
instance IsSource Text    where toSource = Source . FromAtom
instance IsSource Literal where toSource = Source . FromLiteral
instance IsSource Int     where toSource = Source . FromInt
newtype  RegisterF = RegisterF { unRegisterF :: Argument }
class    IsRegisterF a         where toRegisterF :: a -> RegisterF
instance IsRegisterF RegisterF where toRegisterF = id
instance IsRegisterF F         where toRegisterF = RegisterF . FromF
instance IsRegisterF X         where toRegisterF = RegisterF . FromX
instance IsRegisterF Y         where toRegisterF = RegisterF . FromY
newtype  SourceF = SourceF { unSourceF :: Argument }
class    IsSourceF a       where toSourceF :: a -> SourceF
instance IsSourceF SourceF where toSourceF = id
instance IsSourceF F       where toSourceF = SourceF . FromF
instance IsSourceF X       where toSourceF = SourceF . FromX
instance IsSourceF Y       where toSourceF = SourceF . FromY
instance IsSourceF Literal where toSourceF = SourceF . FromLiteral
data Argument
  = FromImport Import
  | FromX X
  | FromY Y
  | FromF F
  | FromNewLabel Label
  | FromUntagged Int
  | FromInt Int
  | FromNil Nil
  | FromAtom Text
  | FromLabel Label
  | FromLiteral Literal
  | FromLambda Lambda
  | FromList [Argument]
  | FromNewFunction Text Int
fromRegister :: IsRegister a => a -> Argument
fromRegister = unRegister . toRegister
fromSource :: IsSource a => a -> Argument
fromSource = unSource . toSource
fromRegisterF :: IsRegisterF a => a -> Argument
fromRegisterF = unRegisterF . toRegisterF
fromSourceF :: IsSourceF a => a -> Argument
fromSourceF = unSourceF . toSourceF
fromDestinations :: [(Label, Source)] -> Argument
fromDestinations =
  FromList . foldr (\x a -> FromLabel (fst x) : fromSource (snd x) : a) []
fromPairs :: (a -> Argument) -> [(a, a)] -> Argument
fromPairs from =
  FromList . foldr (\x a -> from (snd x) : from (fst x) : a) []
class IsBif a where unBif :: Int -> a -> Import