-- | Methods array of a class. {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE DerivingVia #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE InstanceSigs #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE StandaloneKindSignatures #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE UndecidableInstances #-} module Language.Java.Classfile.Methods (Methods(..), Method(..), MethodFlag(..)) where import Data.Array.IArray (Array) import Data.Word (Word16) import Language.Java.Classfile.Flags (Flags, FlagMask (..)) import Language.Java.Classfile.Extractable (Extractable) import GHC.Generics ( Generically, Generic, Generically(..) ) import Language.Java.Classfile.ConstantPool.References (Utf8) import Language.Java.Classfile.Attributes (Attributes) import Pretty.Serialize (PrettySerialize) import Language.Java.Classfile.Stage (Stage) import Data.Kind (Type) import Data.Typeable (Typeable) -- | Alias for the methods structure from the constant-pool. newtype Methods stage = Methods (Array Word16 (Method stage)) deriving stock instance (Show (Utf8 stage), Show (Attributes stage)) => Show (Methods stage) deriving newtype instance (Typeable stage, Extractable (Utf8 stage), Extractable (Attributes stage)) => Extractable (Methods stage) deriving newtype instance (Typeable stage, PrettySerialize (Utf8 stage), PrettySerialize (Attributes stage)) => PrettySerialize (Methods stage) -- | A single method record, contains attributes, name and access flags. type Method :: Stage -> Type data Method stage = Method { flags :: Flags MethodFlag , name :: Utf8 stage , descriptor :: Utf8 stage , attributes :: Attributes stage } deriving stock (Generic) deriving stock instance (Show (Utf8 stage), Show (Attributes stage)) => Show (Method stage) deriving via Generically (Method stage) instance (Extractable (Utf8 stage), Extractable (Attributes stage)) => Extractable (Method stage) deriving via Generically (Method stage) instance (PrettySerialize (Utf8 stage), PrettySerialize (Attributes stage)) => PrettySerialize (Method stage) -- | Flags for the method, such as abstract, public or static. data MethodFlag = Public | Private | Protected | Static | Final | Synchronized | Bridge | Varargs | Native | Abstract | Strict | Synthetic deriving stock (Show, Eq, Ord, Enum, Bounded, Generic) deriving PrettySerialize via Generically MethodFlag instance FlagMask MethodFlag where type FlagType MethodFlag = Word16 maskOf :: MethodFlag -> FlagType MethodFlag maskOf = \case Public -> 0x0001 Private -> 0x0002 Protected -> 0x0004 Static -> 0x0008 Final -> 0x0010 Synchronized -> 0x0020 Bridge -> 0x0040 Varargs -> 0x0080 Native -> 0x0100 Abstract -> 0x0400 Strict -> 0x0800 Synthetic -> 0x1000