derive-prim: Derive Prim and PrimUnaligned

[ data, development, generics, gpl, library ] [ Propose Tags ]

This package provides the newtype GenericPrim which allows user to derive instances for Prim and PrimUnaligned through the DerivingVia extension.


[Skip to Readme]

Modules

[Index] [Quick Jump]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.1.0.0, 0.1.0.1
Change log CHANGELOG.md
Dependencies base (>=4.17.2.0 && <4.20), primitive (>=0.9.0 && <0.10), primitive-unaligned (>=0.1.1 && <0.2) [details]
License GPL-3.0-or-later
Author k355l3r-5yndr0m3
Maintainer hoanghung17jan@gmail.com
Category Data, Generics, Development
Home page https://github.com/k355l3r-5yndr0m3/derive-prim
Bug tracker https://github.com/k355l3r-5yndr0m3/derive-prim/issues
Uploaded by k355l3r5yndr0m3 at 2024-05-12T09:50:27Z
Distributions
Downloads 30 total (30 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2024-05-12 [all 1 reports]

Readme for derive-prim-0.1.0.1

[back to package description]

derive-prim: Derive Prim and PrimUnaligned using Generic

USAGE

Here is an example of how to derive the Prim and PrimUnaligned instance.

{-# LANGUAGE DerivingVia #-}
import Data.Primitive
import Data.Primitive.Generic
import Data.Primitive.ByteArray.Unaligned

data Struct = Struct
  { membChar  :: Char    
  , membInt   :: Int
  , membFloat :: Float
  } derive (Generic)
    derive (Prim, PrimUnaligned) via (GenericPrim Struct)

data OtherStruct = OtherStruct Int Word Float Double Char
    derive (Generic) 
    derive (Prim, PrimUnaligned) via (GenericPrim OtherStruct)

All members must implement both an instance of Prim and an instance of PrimUnaligned. Nested structs are also allowed as long as they implement the nessisary instances.

data Inside = ... 
  derive (Generic) 
  derive (Prim, PrimUnaligned) via (GenericPrim Struct)

data Outside = Outside 
  { ...
  , nested :: Inside
    ...
  } derive (Generic) derive (Prim, PrimUnaligned) via (GenericPrim Struct)

To tweak members placement in memory use Align or Packed.

data Struct = Struct 
  { ...
  , someField :: Align 4 SomeType {- This field will have an alignment of 4 bytes -}
    ...
  , someOtherField :: Packed SomeOtherType {- This field will have an alignment of 1 bytes #-}
  }

The specific offset of a field can be queried by offsetOf @STRUCT_TYPE @RECORD_NAME.

memberOffset :: Int
memberOffset = offsetOf @Struct @"someField"

Details

Members are layout in memory according to their order. Members placed higher will have a lower memory address. Each member's offset will be the lowest offset respecting its alignment such that no overlapping between previous members occur. The alignment of the structure is the least common multiple of all its members' alignments. The size of the structures is rounded up to the nearest multiple of the structure's alignment.

Currently, only data types with one constructor are supported.