Skip to content

Commit

Permalink
tweaks
Browse files Browse the repository at this point in the history
  • Loading branch information
raehik committed Mar 17, 2024
1 parent 4c7622d commit 13ae56d
Show file tree
Hide file tree
Showing 5 changed files with 17 additions and 14 deletions.
6 changes: 3 additions & 3 deletions flake.lock

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

3 changes: 3 additions & 0 deletions src/Binrep/BLen.hs
Original file line number Diff line number Diff line change
Expand Up @@ -34,6 +34,7 @@ import Data.Void
import Data.ByteString qualified as B
import Data.Word
import Data.Int
import Binrep.Util.ByteOrder

import Data.Monoid ( Sum(..) )
import GHC.Generics
Expand Down Expand Up @@ -104,6 +105,8 @@ deriving via ViaCBLen Word32 instance BLen Word32
deriving via ViaCBLen Int32 instance BLen Int32
deriving via ViaCBLen Word64 instance BLen Word64
deriving via ViaCBLen Int64 instance BLen Int64
deriving via ViaCBLen (ByteOrdered end a)
instance KnownNat (CBLen a) => BLen (ByteOrdered end a)

--------------------------------------------------------------------------------

Expand Down
7 changes: 5 additions & 2 deletions src/Binrep/CBLen.hs
Original file line number Diff line number Diff line change
@@ -1,11 +1,11 @@
{-# LANGUAGE UndecidableInstances #-} -- for 'WithCBLen'
{-# LANGUAGE AllowAmbiguousTypes #-} -- for 'cblen'
{-# LANGUAGE UndecidableInstances #-} -- for nested type families

module Binrep.CBLen where

import GHC.TypeNats
import Data.Word
import Data.Int
import Binrep.Util.ByteOrder

class IsCBLen a where type CBLen a :: Natural

Expand All @@ -21,3 +21,6 @@ instance IsCBLen Word32 where type CBLen Word32 = 2^2
instance IsCBLen Int32 where type CBLen Int32 = 2^2
instance IsCBLen Word64 where type CBLen Word64 = 2^3
instance IsCBLen Int64 where type CBLen Int64 = 2^3

instance IsCBLen a => IsCBLen (ByteOrdered end a) where
type CBLen (ByteOrdered end a) = CBLen a
6 changes: 3 additions & 3 deletions test/ArbitraryOrphans.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,9 +3,9 @@
module ArbitraryOrphans() where

import Test.QuickCheck ( Arbitrary )
import Binrep.Type.Int
import Data.Kind
import Binrep.Util.ByteOrder ( ByteOrdered(..) )
import Data.Kind ( Type )

-- TODO 2023-01-26 raehik: why does the following crash GHC
deriving via (a :: Type) instance Arbitrary a => Arbitrary (Endian end a)
deriving via (a :: Type) instance Arbitrary a => Arbitrary (ByteOrdered end a)
--deriving newtype instance Arbitrary a => Arbitrary (Endian end a)
9 changes: 3 additions & 6 deletions test/Binrep/LawsSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,10 +11,7 @@ import ArbitraryOrphans()

import Binrep
import Binrep.Generic ( nullTermCstrPfxTag )
import Binrep.BLen.Simple ( blenGenericNonSum, blenGenericSum )
import Binrep.Type.Int
import Binrep.Type.Common ( Endianness(..) )
import Binrep.Type.NullTerminated
import Binrep.Util.ByteOrder
import Data.Word
import Data.ByteString qualified as B
import GHC.Generics ( Generic )
Expand All @@ -33,8 +30,8 @@ spec = do
--------------------------------------------------------------------------------

type W1 = Word8
type W2LE = Endian 'LE Word16
type W8BE = Endian 'BE Word64
type W2LE = ByteOrdered LE Word16
type W8BE = ByteOrdered BE Word64

data D
= D01Bla Word8 W1 W8BE
Expand Down

0 comments on commit 13ae56d

Please sign in to comment.