Compare commits

..

No commits in common. "500bfa349ea782011b26546d98b1b9888adcb731" and "547187e4289e55ea26696497c7bcd90bcb9fe6bf" have entirely different histories.

21 changed files with 62 additions and 148 deletions

3
.gitmodules vendored
View file

@ -1,3 +0,0 @@
[submodule "3rdparty/pretty-parse"]
path = 3rdparty/pretty-parse
url = https://git.jossco.de/vegowotenks/pretty-parse

@ -1 +0,0 @@
Subproject commit a7bff630fc3e5e140274fb65d6b88b46e7a086eb

View file

@ -4,8 +4,6 @@
module Main (main) where
import Data.ByteString.Lazy qualified as ByteString
import Data.Text.Lazy.IO qualified as LazyTextIO
import Pretty.Serialize qualified as Pretty
import Language.Java.Classfile (Classfile)
import Language.Java.Classfile.Extract (runExtract)
@ -15,4 +13,4 @@ import Language.Java.Classfile.Stage (Stage(Parse))
main :: IO ()
main = do
input <- ByteString.getContents
LazyTextIO.putStrLn . Pretty.serialize $ runExtract input (extract @(Classfile Parse))
print $ runExtract input (extract @(Classfile Parse))

View file

@ -44,13 +44,12 @@ library
Paths_java_classfile
hs-source-dirs:
src
ghc-options: -Wall -Wcompat -Widentities -Wincomplete-record-updates -Wincomplete-uni-patterns -Wmissing-export-lists -Wmissing-home-modules -Wpartial-fields -Wredundant-constraints -Wunused-packages
ghc-options: -Wall -Wcompat -Widentities -Wincomplete-record-updates -Wincomplete-uni-patterns -Wmissing-export-lists -Wmissing-home-modules -Wpartial-fields -Wredundant-constraints
build-depends:
array
, base >=4.7 && <5
, bytestring
, containers
, pretty-parse
, text
default-language: Haskell2010
@ -60,12 +59,13 @@ executable java-classfile-exe
Paths_java_classfile
hs-source-dirs:
app
ghc-options: -Wall -Wcompat -Widentities -Wincomplete-record-updates -Wincomplete-uni-patterns -Wmissing-export-lists -Wmissing-home-modules -Wpartial-fields -Wredundant-constraints -Wunused-packages -threaded -rtsopts -with-rtsopts=-N
ghc-options: -Wall -Wcompat -Widentities -Wincomplete-record-updates -Wincomplete-uni-patterns -Wmissing-export-lists -Wmissing-home-modules -Wpartial-fields -Wredundant-constraints -threaded -rtsopts -with-rtsopts=-N
build-depends:
base >=4.7 && <5
array
, base >=4.7 && <5
, bytestring
, containers
, java-classfile
, pretty-parse
, text
default-language: Haskell2010
@ -76,9 +76,12 @@ test-suite java-classfile-test
Paths_java_classfile
hs-source-dirs:
test
ghc-options: -Wall -Wcompat -Widentities -Wincomplete-record-updates -Wincomplete-uni-patterns -Wmissing-export-lists -Wmissing-home-modules -Wpartial-fields -Wredundant-constraints -Wunused-packages -threaded -rtsopts -with-rtsopts=-N
ghc-options: -Wall -Wcompat -Widentities -Wincomplete-record-updates -Wincomplete-uni-patterns -Wmissing-export-lists -Wmissing-home-modules -Wpartial-fields -Wredundant-constraints -threaded -rtsopts -with-rtsopts=-N
build-depends:
base >=4.7 && <5
array
, base >=4.7 && <5
, bytestring
, containers
, java-classfile
, text
default-language: Haskell2010

View file

@ -19,8 +19,11 @@ synopsis: Multi-Stage classfile parsing and verification.
description: Please see the README on Forgejo at <https://git.jossco.de/vegowotenks/java-classfile#readme>
dependencies:
- array
- base >= 4.7 && < 5
- bytestring
- containers
- text
ghc-options:
- -Wall
@ -32,15 +35,9 @@ ghc-options:
- -Wmissing-home-modules
- -Wpartial-fields
- -Wredundant-constraints
- -Wunused-packages
library:
source-dirs: src
dependencies:
- array
- containers
- pretty-parse
- text
executables:
java-classfile-exe:
@ -52,8 +49,6 @@ executables:
- -with-rtsopts=-N
dependencies:
- java-classfile
- pretty-parse
- text
tests:
java-classfile-test:

View file

@ -11,7 +11,6 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Language.Java.Classfile (Classfile(..)) where
import GHC.Generics (Generic, Generically(Generically))
@ -30,7 +29,6 @@ import Language.Java.Classfile.Fields (Fields)
import Language.Java.Classfile.Methods (Methods)
import Language.Java.Classfile.Attributes (Attributes)
import Data.Word (Word16)
import Pretty.Serialize (PrettySerialize)
-- | 'Stage'-indexed classfile. It can represent a class, an interface or a module.
@ -52,7 +50,6 @@ data Classfile stage = Classfile
deriving instance (Show (Magic stage), Show (ConstantPool stage), Show (ClassFlags stage), Show (Class stage)) => Show (Classfile stage)
deriving via Generically (Classfile Parse) instance (Extractable (Classfile Parse))
deriving via Generically (Classfile Parse) instance (PrettySerialize (Classfile Parse))
type ClassFlags :: Stage -> Type
data family ClassFlags stage
@ -60,20 +57,18 @@ data family ClassFlags stage
newtype instance ClassFlags Parse = ClassFlags (Flags ClassFlag)
deriving stock (Show, Generic)
deriving Extractable via Generically (ClassFlags Parse)
deriving newtype PrettySerialize
data ClassFlag
= Public -- ^ may be accessed from outside the package
| Final -- ^ no subclasses allowed
| Super -- ^ treat superclass methods special when using InvokeSpecial
| Interface -- ^ is an interface
| Abstract -- ^ abstract, must not be instantiated
| Synthetic -- ^ not present in source code
| Annotation -- ^ is annotation interface
| Enum -- ^ enumerated instances
| Module -- ^ module, not a class
deriving (Show, Eq, Ord, Enum, Bounded, Generic)
deriving PrettySerialize via Generically ClassFlag
= Public
| Final
| Super
| Interface
| Abstract
| Synthetic
| Annotation
| Enum
| Module
deriving (Show, Eq, Ord, Enum, Bounded)
instance FlagMask ClassFlag where
type FlagType ClassFlag = Word16

View file

@ -10,7 +10,6 @@ import Language.Java.Classfile.Extractable (Extractable)
import Language.Java.Classfile.ConstantPool.References (Utf8Reference)
import Language.Java.Classfile.Extractable.SizedBytes (SizedBytes)
import GHC.Generics ( Generic, Generically(..) )
import Pretty.Serialize (PrettySerialize)
-- | Generic Attribute array used everywhere.
--
@ -18,7 +17,7 @@ import Pretty.Serialize (PrettySerialize)
newtype Attributes = Attributes (Array Word16 Attribute)
deriving stock (Show)
deriving newtype (Extractable, PrettySerialize)
deriving newtype Extractable
-- | Unknown Attribute
@ -27,4 +26,4 @@ data Attribute = Attribute
, info :: SizedBytes Word32
}
deriving stock (Show, Generic)
deriving (Extractable, PrettySerialize) via Generically Attribute
deriving Extractable via Generically Attribute

View file

@ -1,5 +1,6 @@
-- | THE constant pool, all the constants in a class file are handled in here.
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE OverloadedStrings #-}
@ -9,8 +10,6 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE DeriveGeneric #-}
module Language.Java.Classfile.ConstantPool (ConstantPool(..)) where
import Data.Word (Word16)
import Data.Array.IArray (Array, listArray)
@ -20,19 +19,13 @@ import Language.Java.Classfile.Extract (Extract, traceIndex, traceType)
import qualified Data.Text as Text
import Language.Java.Classfile.Stage (Stage(..))
import Data.Kind (Type)
import GHC.Generics (Generically(..), Generic)
import Pretty.Serialize (PrettySerialize)
type ConstantPool :: Stage -> Type
data family ConstantPool stage
newtype instance ConstantPool Parse = ConstantPool (Array Word16 Entry)
deriving stock (Generic, Show)
deriving via (Generically (ConstantPool Parse)) instance PrettySerialize (ConstantPool Parse)
data instance ConstantPool Resolve = NoPool
data ConstantPool stage where
ConstantPool :: (Array Word16 Entry) -> ConstantPool Parse
NoPool :: ConstantPool Resolve
deriving instance Show (ConstantPool stage)
-- | 'Stage'-indexed constant-pool. The constant-pool is erased after resolving the class file.

View file

@ -8,7 +8,6 @@
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OrPatterns #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Language.Java.Classfile.ConstantPool.Entry (Entry(..), StorageCount(..), storageCount, MethodHandleInfo(..)) where
import GHC.Generics (Generic, Generically(..))
import Language.Java.Classfile.Extractable (Extractable (extract))
@ -21,7 +20,6 @@ import Language.Java.Classfile.Extract (Extract, bytes)
import qualified Data.Text.Encoding as Text
import qualified Data.ByteString.Lazy as ByteString
import qualified Data.ByteString as StrictByteString
import Pretty.Serialize (PrettySerialize)
-- | A single entry. Double and Long are not followed by something unusable, they are duplicated instead.
@ -62,7 +60,6 @@ data Entry
-- ^ Some package description
deriving stock (Show, Generic)
deriving Extractable via Generically Entry
deriving PrettySerialize via Generically Entry
-- | Holds the invariants of MethodHandles (Only certain references are allowed after some kinds)
--
@ -71,13 +68,11 @@ data Entry
data MethodHandleInfo = MethodHandleInfo MethodHandleReferenceKind OpaqueReference
deriving stock (Show, Generic)
deriving Extractable via Generically MethodHandleInfo
deriving PrettySerialize via Generically MethodHandleInfo
-- | Extractor newtype for a java-utf-text with size tag specified as a type argument.
newtype SizedText sizeType = SizedText Text
deriving stock (Show)
deriving newtype PrettySerialize
instance (Integral sizeType, Extractable sizeType) => Extractable (SizedText sizeType) where
extract :: Extract (SizedText sizeType)

View file

@ -7,7 +7,6 @@
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE StandaloneKindSignatures #-}
{-# LANGUAGE DeriveGeneric #-}
module Language.Java.Classfile.ConstantPool.References (Utf8Reference(..), ClassReference(..), NameAndTypeReference(..), MethodHandleReferenceKind(..), OpaqueReference(..), BootstrapMethodIndex(..), Class) where
import Data.Word (Word16, Word8)
import Language.Java.Classfile.Extractable (Extractable)
@ -15,15 +14,12 @@ import Language.Java.Classfile.Extractable.AsTag
( TagValue(..), AsTag, AsTag(..) )
import Language.Java.Classfile.Stage (Stage(..))
import Data.Kind (Type)
import Pretty.Serialize (PrettySerialize)
import GHC.Generics (Generically(..), Generic)
-- | Wrapper for constant-pool reference to text.
newtype Utf8Reference = Utf8Reference Word16
deriving stock (Show, Generic)
deriving stock (Show)
deriving newtype Extractable
deriving PrettySerialize via Generically Utf8Reference
-- | 'Stage'-indexed type, either a Class or only a t'ClassReference'.
@ -34,30 +30,26 @@ type family Class stage where
-- | Reference to a class in a constant-pool. This will resolve into a class.
newtype ClassReference = ClassReference Word16
deriving stock (Show, Generic)
deriving stock (Show)
deriving newtype Extractable
deriving PrettySerialize via Generically ClassReference
-- | Reference to a class in a constant-pool. This will resolve to Name and Type.
newtype NameAndTypeReference = NameAndTypeReference Word16
deriving stock (Show, Generic)
deriving stock (Show)
deriving newtype Extractable
deriving PrettySerialize via Generically NameAndTypeReference
-- | Reference to something in a constant-pool. I will hopefully get rid of this type.
newtype OpaqueReference = OpaqueReference Word16
deriving stock (Show, Generic)
deriving stock (Show)
deriving newtype Extractable
deriving PrettySerialize via Generically OpaqueReference
-- | Reference to a method in the BootstrapMethods class attribute
newtype BootstrapMethodIndex = BootstrapMethodIndex Word16
deriving stock (Show, Generic)
deriving stock (Show)
deriving newtype Extractable
deriving PrettySerialize via Generically BootstrapMethodIndex
-- | A Tag used to determine the type of a MethodHandle
@ -71,9 +63,8 @@ data MethodHandleReferenceKind
| InvokeSpecial
| NewInvokeSpecial
| InvokeInterface
deriving stock (Show, Enum, Bounded, Generic)
deriving stock (Show, Enum, Bounded)
deriving Extractable via AsTag MethodHandleReferenceKind
deriving PrettySerialize via Generically MethodHandleReferenceKind
instance TagValue MethodHandleReferenceKind where
type TagType MethodHandleReferenceKind = Word8

View file

@ -2,30 +2,19 @@
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE DeriveGeneric #-}
module Language.Java.Classfile.Extract (Extract(), bytes, runExtract, expectRaw, expectEqual, traceType, traceConstructor, traceField, traceIndex, Reason(..), Trace(..), Expected(..), Actual(..), TypeName(..)) where
import Control.Applicative (Alternative (empty, (<|>)))
import Control.Monad (MonadPlus)
import GHC.Generics (Generic, Generically(..))
import Data.ByteString.Lazy (ByteString)
import Data.Text (Text)
import Data.Typeable (Typeable, typeOf)
import Pretty.Serialize (PrettySerialize)
import qualified Data.ByteString.Lazy as ByteString
import Control.Applicative (Alternative (empty, (<|>)))
import Data.Text (Text)
import qualified Data.Text as Text
import Data.Typeable (Typeable, typeOf)
-- | Extractor Monad. Computations running in this monad will automatically keep track of used resources and backtrack arbitrarily.
newtype Extract a = Extract (Continuation a)
deriving (Functor)
deriving anyclass MonadPlus
-- | Functions work wonders when defining monads.
@ -40,18 +29,15 @@ data Reply a
-- | Type Alias for the Show instance
newtype Expected = Expected Text
deriving stock (Show, Generic)
deriving PrettySerialize via Generically Expected
deriving Show
-- | Type Alias for the Show instance
newtype Actual = Actual Text
deriving stock (Show, Generic)
deriving PrettySerialize via Generically Actual
deriving Show
-- | Type Alias for the Show instance
newtype TypeName = TypeName Text
deriving stock (Show, Generic)
deriving PrettySerialize via Generically TypeName
deriving Show
-- | Why did the computation fail?
@ -64,8 +50,7 @@ data Reason
-- ^ Something else went wrong
| Unknown
-- ^ Someone used the 'empty' function from 'Alternative'
deriving stock (Show, Generic)
deriving PrettySerialize via Generically Reason
deriving Show
-- | Where did the computation fail? Calls to these functions are auto-generated by the Generic instances.
@ -74,8 +59,7 @@ data Trace
| InConstructor Text
| InField Text
| AtIndex Word
deriving stock (Show, Generic)
deriving PrettySerialize via Generically Trace
deriving Show
instance Applicative Extract where
-- | Don't consume any input

View file

@ -1,22 +1,20 @@
-- | Read arbitrary bytes prefixed with a length.
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE DerivingVia #-}
module Language.Java.Classfile.Extractable.SizedBytes (SizedBytes(..)) where
import Data.ByteString (ByteString)
import Language.Java.Classfile.Extractable (Extractable (..))
import Language.Java.Classfile.Extract (Extract, bytes)
import qualified Data.ByteString as StrictByteString
import qualified Data.ByteString.Lazy as ByteString
import Pretty.Serialize (PrettySerialize, ShowPrettySerialize(..))
-- | The sizeType type Paramter is used to extract the correct byte count.
newtype SizedBytes sizeType = SizedBytes ByteString
deriving stock Show
deriving PrettySerialize via ShowPrettySerialize (SizedBytes sizeType)
instance (Extractable sizeType, Integral sizeType) => Extractable (SizedBytes sizeType) where
extract :: Extract (SizedBytes sizeType)

View file

@ -16,7 +16,6 @@ import Control.Monad (void)
import Data.Proxy (Proxy(Proxy))
import Data.Typeable ( Typeable )
import Data.Word (Word8)
import Pretty.Serialize (PrettySerialize)
-- | Type alias if you use the same type a lot.
@ -26,7 +25,7 @@ type Word8Tag value a = WithNumericTag value Word8 a
type WithNumericTag :: Natural -> Type -> Type -> Type
newtype WithNumericTag value tagType a = Tagged a
deriving newtype (Show, PrettySerialize)
deriving newtype Show
instance (KnownNat value, Extractable a, Extractable tagType, Eq tagType, Num tagType, Show tagType, Typeable tagType) => Extractable (WithNumericTag value tagType a) where
extract :: Extract (WithNumericTag value tagType a)

View file

@ -14,13 +14,12 @@ import GHC.Generics ( Generically, Generic, Generically(..) )
import Language.Java.Classfile.Flags (Flags, FlagMask (..))
import Language.Java.Classfile.ConstantPool.References (Utf8Reference)
import Language.Java.Classfile.Attributes (Attributes)
import Pretty.Serialize (PrettySerialize)
-- | Word16-Array of Fields.
newtype Fields = Fields (Array Word16 Field)
deriving stock Show
deriving newtype (Extractable, PrettySerialize)
deriving newtype Extractable
-- | All the access flags a field can have
@ -34,8 +33,7 @@ data FieldFlag
| Transient
| Synthetic
| Enumeration -- original "Enum"
deriving stock (Show, Eq, Ord, Enum, Bounded, Generic)
deriving PrettySerialize via Generically FieldFlag
deriving stock (Show, Eq, Ord, Enum, Bounded)
instance FlagMask FieldFlag where
type FlagType FieldFlag = Word16
@ -60,4 +58,4 @@ data Field = Field
, attribute :: Attributes
}
deriving stock (Show, Generic)
deriving (Extractable, PrettySerialize) via Generically Field
deriving Extractable via Generically Field

View file

@ -6,13 +6,10 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Language.Java.Classfile.Flags (Flags(..), FlagMask(..), containsFlag) where
module Language.Java.Classfile.Flags (Flags(..), FlagMask(..)) where
import Data.Bits (Bits((.&.), zeroBits))
import Data.Bits (Bits((.&.)))
import Data.Enum.Util (enumerate)
import Data.Set (Set)
@ -21,15 +18,11 @@ import qualified Data.Set as Set
import Language.Java.Classfile.Extract (Extract)
import Language.Java.Classfile.Extractable (Extractable (extract))
import Data.Kind (Type)
import Control.Arrow ((>>>))
import qualified Data.List as List
import Pretty.Serialize (PrettySerialize)
-- | Using the 'FlagMask' instance of the type parameter, this will extract all the flags whose mask produced a non-zero value using '.&.'
newtype Flags a = Flags (Set a)
deriving (Show)
deriving newtype PrettySerialize
instance (Extractable (FlagType a), Bounded a, Enum a, Ord a, FlagMask a, Bits (FlagType a), Num (FlagType a)) => Extractable (Flags a) where
extract :: Extract (Flags a)
@ -46,13 +39,3 @@ class FlagMask a where
type FlagType a :: Type
maskOf :: a -> FlagType a
ofMask :: FlagType a -> Set a
default ofMask :: (Enum a, Bounded a, Ord a, Bits (FlagType a)) => FlagType a -> Set a
ofMask mask = List.filter (containsFlag mask)
>>> Set.fromList
$ enumerate @a
containsFlag :: (Bits (FlagType a), FlagMask a) => FlagType a -> a -> Bool
containsFlag mask flag = mask .&. maskOf flag /= zeroBits

View file

@ -8,10 +8,9 @@ import Data.Word (Word16)
import Language.Java.Classfile.ConstantPool.References (ClassReference)
import Language.Java.Classfile.Extractable (Extractable)
import GHC.Generics ( Generic, Generically, Generically(..) )
import Pretty.Serialize (PrettySerialize)
-- | A list of classes something implements.
newtype Interfaces = Interfaces (Array Word16 ClassReference)
deriving stock (Show, Generic)
deriving (Extractable, PrettySerialize) via Generically Interfaces
deriving Extractable via Generically Interfaces

View file

@ -6,8 +6,6 @@
{-# LANGUAGE StandaloneKindSignatures #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE DerivingVia #-}
module Language.Java.Classfile.Magic (Magic(..)) where
import Data.Word (Word32)
import Language.Java.Classfile.Extractable (Extractable, extract, expectConstant)
@ -15,7 +13,6 @@ import Language.Java.Classfile.Extract (Extract)
import Data.Hex (Hex (Hex))
import Language.Java.Classfile.Stage (Stage(Parse, Resolve))
import Data.Kind (Type)
import Pretty.Serialize (ShowPrettySerialize(ShowPrettySerialize), PrettySerialize)
-- | 'Stage'-indexed Magic type. The 'Resolve' stage is only a unit type.
@ -24,9 +21,6 @@ data Magic stage where
Magic :: Hex Word32 -> Magic Parse
Cafebabe :: Magic Resolve
deriving instance Show (Magic stage)
deriving via ShowPrettySerialize (Magic stage) instance PrettySerialize (Magic stage)
instance Extractable (Magic Parse) where
extract :: Extract (Magic Parse)
extract = Magic . Hex <$> expectConstant 0xCAFEBABE

View file

@ -14,13 +14,12 @@ import Language.Java.Classfile.Extractable (Extractable)
import GHC.Generics ( Generically, Generic, Generically(..) )
import Language.Java.Classfile.ConstantPool.References (Utf8Reference)
import Language.Java.Classfile.Attributes (Attributes)
import Pretty.Serialize (PrettySerialize)
-- | Alias for the methods structure from the constant-pool.
newtype Methods = Methods (Array Word16 Method)
deriving stock (Show)
deriving newtype (Extractable, PrettySerialize)
deriving newtype Extractable
-- | A single method record, contains attributes, name and access flags.
@ -31,7 +30,7 @@ data Method = Method
, attributes :: Attributes
}
deriving stock (Show, Generic)
deriving (Extractable, PrettySerialize) via Generically Method
deriving Extractable via Generically Method
-- | Flags for the method, such as abstract, public or static.
@ -48,8 +47,7 @@ data MethodFlag
| Abstract
| Strict
| Synthetic
deriving stock (Show, Eq, Ord, Enum, Bounded, Generic)
deriving PrettySerialize via Generically MethodFlag
deriving stock (Show, Eq, Ord, Enum, Bounded)
instance FlagMask MethodFlag where
type FlagType MethodFlag = Word16

View file

@ -7,7 +7,6 @@ module Language.Java.Classfile.Version (Version(..)) where
import Data.Word (Word16)
import GHC.Generics (Generic, Generically(Generically))
import Language.Java.Classfile.Extractable (Extractable)
import Pretty.Serialize (PrettySerialize)
-- | Classfile versions only have two components. The minor component is zero since some java version.
@ -16,7 +15,7 @@ data Version = Version
, major :: Word16
}
deriving stock (Show, Generic)
deriving (Extractable, PrettySerialize) via Generically Version
deriving Extractable via Generically Version
-- >>> import Language.Java.Classfile.Extractable (Extractable(extract))
-- >>> import Language.Java.Classfile.Extract (runExtract, Extract)

View file

@ -17,8 +17,7 @@
#
# snapshot: ./custom-snapshot.yaml
# snapshot: https://example.com/snapshots/2024-01-01.yaml
snapshot:
url: https://raw.githubusercontent.com/commercialhaskell/stackage-snapshots/master/lts/24/3.yaml
snapshot: nightly-2025-07-10
compiler: ghc-9.12.1
# User packages to be built.
@ -32,7 +31,6 @@ compiler: ghc-9.12.1
# - wai
packages:
- .
- 3rdparty/pretty-parse
# Dependency packages to be pulled from upstream that are not in the snapshot.
# These entries can reference officially published versions as well as
# forks / in-progress versions pinned to a git hash. For example:

View file

@ -6,8 +6,7 @@
packages: []
snapshots:
- completed:
sha256: aa97dce5253937e4aa56100a0a9dc1f79a554cf543ad7cfab0afe6ed42de2f31
size: 724941
url: https://raw.githubusercontent.com/commercialhaskell/stackage-snapshots/master/lts/24/3.yaml
original:
url: https://raw.githubusercontent.com/commercialhaskell/stackage-snapshots/master/lts/24/3.yaml
sha256: 39e3a4dc79edf153bb0aa6dc4206b1543c0e0f3e3811ec751abdcdf3aaf08887
size: 723871
url: https://raw.githubusercontent.com/commercialhaskell/stackage-snapshots/master/nightly/2025/7/10.yaml
original: nightly-2025-07-10