feat: Alternative instance + Generic work
This commit is contained in:
parent
5723a92308
commit
7a20aeeca2
2 changed files with 25 additions and 1 deletions
|
@ -4,6 +4,7 @@ module Language.Java.Classfile.Extract (Extract(), bytes) where
|
|||
|
||||
import Data.ByteString.Lazy (ByteString)
|
||||
import qualified Data.ByteString.Lazy as ByteString
|
||||
import Control.Applicative (Alternative (empty, (<|>)))
|
||||
|
||||
data Extract a = Extract (Continuation a)
|
||||
|
||||
|
@ -28,6 +29,14 @@ instance Applicative Extract where
|
|||
Fail -> Fail
|
||||
Fail -> Fail
|
||||
|
||||
instance Alternative Extract where
|
||||
empty :: Extract a
|
||||
empty = Extract $ const Fail
|
||||
(<|>) :: Extract a -> Extract a -> Extract a
|
||||
(<|>) (Extract left) (Extract right) = Extract $ \ input -> case left input of
|
||||
Fail -> right input
|
||||
t -> t
|
||||
|
||||
|
||||
-- | Get a specified count of bytes. Fail if there are not enough bytes available.
|
||||
|
||||
|
|
|
@ -1,11 +1,13 @@
|
|||
{-# LANGUAGE InstanceSigs #-}
|
||||
{-# LANGUAGE TypeOperators #-}
|
||||
module Language.Java.Classfile.Extractable () where
|
||||
import Language.Java.Classfile.Extract (Extract, bytes)
|
||||
import Data.Word (Word8, Word16, Word32)
|
||||
import qualified Data.ByteString.Lazy as ByteString
|
||||
import Data.ByteString.Lazy (ByteString)
|
||||
import Data.Bits (Bits(shiftL, (.|.)))
|
||||
import GHC.Generics (U1 (U1))
|
||||
import GHC.Generics (U1 (U1), (:*:))
|
||||
import Control.Applicative ((<|>))
|
||||
|
||||
|
||||
class Extractable a where
|
||||
|
@ -29,3 +31,16 @@ build = ByteString.foldl' shiftOr 0
|
|||
shiftOr :: (Bits a1, Num a1) => a1 -> Word8 -> a1
|
||||
shiftOr word appendix = shiftL word 8 .|. fromIntegral appendix
|
||||
|
||||
class GenericExtractable a where
|
||||
genericExtract :: Extract (a i)
|
||||
|
||||
-- unit data types
|
||||
instance GenericExtractable U1 where
|
||||
genericExtract :: Extract (U1 i)
|
||||
genericExtract = pure U1
|
||||
|
||||
-- product types
|
||||
instance GenericExtractable (l :*: r) where
|
||||
genericExtract :: Extract ((:*:) l r i)
|
||||
genericExtract = genericExtract <|> genericExtract
|
||||
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue