{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
module Language.JVM.Attribute.ConstantValue
( ConstantValue(..)
)
where
import Language.JVM.Attribute.Base
import Language.JVM.Constant
import Language.JVM.Staged
instance IsAttribute (ConstantValue Low) where
attrName = Const "ConstantValue"
newtype ConstantValue r = ConstantValue
{ constantValue :: Ref JValue r
}
instance Staged ConstantValue where
evolve (ConstantValue r) = ConstantValue <$> link r
devolve (ConstantValue r) = ConstantValue <$> unlink r
$(deriveBaseWithBinary ''ConstantValue)