{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE StandaloneDeriving #-}
module Language.JVM.Attribute.BootstrapMethods
( BootstrapMethods (..)
, methods
, BootstrapMethod (..)
) where
import Language.JVM.Constant
import Language.JVM.Attribute.Base
import Language.JVM.Staged
import Language.JVM.Utils
instance IsAttribute (BootstrapMethods Low) where
attrName = Const "BootstrapMethods"
newtype BootstrapMethods r = BootstrapMethods
{ methods' :: SizedList16 (BootstrapMethod r)
}
methods :: BootstrapMethods r -> [ BootstrapMethod r ]
methods = unSizedList . methods'
data BootstrapMethod r = BootstrapMethod
{ method :: !(DeepRef MethodHandle r)
, arguments :: !(SizedList16 (Ref JValue r))
}
instance Staged BootstrapMethods where
stage f (BootstrapMethods m) =
label "BootstrapMethods" $ BootstrapMethods <$> mapM f m
instance Staged BootstrapMethod where
evolve (BootstrapMethod a m) =
BootstrapMethod <$> link a <*> mapM link m
devolve (BootstrapMethod a m) =
BootstrapMethod <$> unlink a <*> mapM unlink m
$(deriveBaseWithBinary ''BootstrapMethod)
$(deriveBaseWithBinary ''BootstrapMethods)