fix[PrettySerialize]: Optic changes
This commit is contained in:
parent
5e6736e8da
commit
500bfa349e
3 changed files with 6 additions and 7 deletions
2
3rdparty/pretty-parse
vendored
2
3rdparty/pretty-parse
vendored
|
@ -1 +1 @@
|
||||||
Subproject commit 93473c9ac69c20053d9fbe1b8a0ee199980cc435
|
Subproject commit a7bff630fc3e5e140274fb65d6b88b46e7a086eb
|
|
@ -11,6 +11,7 @@
|
||||||
{-# LANGUAGE TypeFamilies #-}
|
{-# LANGUAGE TypeFamilies #-}
|
||||||
{-# LANGUAGE LambdaCase #-}
|
{-# LANGUAGE LambdaCase #-}
|
||||||
{-# LANGUAGE InstanceSigs #-}
|
{-# LANGUAGE InstanceSigs #-}
|
||||||
|
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||||
module Language.Java.Classfile (Classfile(..)) where
|
module Language.Java.Classfile (Classfile(..)) where
|
||||||
|
|
||||||
import GHC.Generics (Generic, Generically(Generically))
|
import GHC.Generics (Generic, Generically(Generically))
|
||||||
|
@ -59,7 +60,7 @@ data family ClassFlags stage
|
||||||
newtype instance ClassFlags Parse = ClassFlags (Flags ClassFlag)
|
newtype instance ClassFlags Parse = ClassFlags (Flags ClassFlag)
|
||||||
deriving stock (Show, Generic)
|
deriving stock (Show, Generic)
|
||||||
deriving Extractable via Generically (ClassFlags Parse)
|
deriving Extractable via Generically (ClassFlags Parse)
|
||||||
deriving PrettySerialize via Generically (ClassFlags Parse)
|
deriving newtype PrettySerialize
|
||||||
|
|
||||||
data ClassFlag
|
data ClassFlag
|
||||||
= Public -- ^ may be accessed from outside the package
|
= Public -- ^ may be accessed from outside the package
|
||||||
|
|
|
@ -7,9 +7,8 @@
|
||||||
{-# LANGUAGE UndecidableInstances #-}
|
{-# LANGUAGE UndecidableInstances #-}
|
||||||
{-# LANGUAGE TypeFamilies #-}
|
{-# LANGUAGE TypeFamilies #-}
|
||||||
{-# LANGUAGE DefaultSignatures #-}
|
{-# LANGUAGE DefaultSignatures #-}
|
||||||
{-# LANGUAGE DeriveGeneric #-}
|
|
||||||
{-# LANGUAGE DerivingVia #-}
|
{-# LANGUAGE DerivingVia #-}
|
||||||
{-# LANGUAGE StandaloneDeriving #-}
|
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||||
module Language.Java.Classfile.Flags (Flags(..), FlagMask(..), containsFlag) where
|
module Language.Java.Classfile.Flags (Flags(..), FlagMask(..), containsFlag) where
|
||||||
|
|
||||||
|
|
||||||
|
@ -24,14 +23,13 @@ import Language.Java.Classfile.Extractable (Extractable (extract))
|
||||||
import Data.Kind (Type)
|
import Data.Kind (Type)
|
||||||
import Control.Arrow ((>>>))
|
import Control.Arrow ((>>>))
|
||||||
import qualified Data.List as List
|
import qualified Data.List as List
|
||||||
import GHC.Generics (Generic, Generically(..))
|
|
||||||
import Pretty.Serialize (PrettySerialize)
|
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 '.&.'
|
-- | 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)
|
newtype Flags a = Flags (Set a)
|
||||||
deriving (Show, Generic)
|
deriving (Show)
|
||||||
deriving via Generically (Flags a) instance (PrettySerialize (Set a)) => PrettySerialize (Flags a)
|
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
|
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)
|
extract :: Extract (Flags a)
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue