scalie/src/Language/Scalie/Bytecode/Object.hs

21 lines
873 B
Haskell

{-# LANGUAGE Trustworthy #-} -- Trustworthy because it imports Vector but does not do unsafe things
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
-- | This module describes a Bytecode Object, similar to a java classfile. It will hold source information, shared constants and
module Language.Scalie.Bytecode.Object (Object(..)) where
import Data.Kind (Type)
import Data.Vector (Vector)
import Language.Scalie.Ast.Provenance (Provenance)
import Language.Scalie.Bytecode.Instruction (Instruction)
import Language.Scalie.Ast.Provenance.SourceLocation (SourceLocation)
import Text.Show (Show)
import Text.Read (Read)
import Data.Semigroup (Semigroup)
import Data.Monoid (Monoid)
type Object :: Type
type role Object
newtype Object = Object { instructions :: Vector (Provenance SourceLocation Instruction) }
deriving stock (Show, Read)
deriving newtype (Semigroup, Monoid)