minimal viable product

This commit is contained in:
vegowotenks 2025-05-02 22:15:46 +02:00
commit afbec2ab33
12 changed files with 413 additions and 0 deletions

View file

@ -0,0 +1,70 @@
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE StandaloneKindSignatures #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE FlexibleContexts #-}
{-# OPTIONS_GHC -Wno-unsafe #-}
module GHC.Generics.Coerce
(GenericCoerce(..), genericCoerce)
where
import Prelude (id, ($), (.))
import GHC.Generics (U1, (:*:) ((:*:)), (:+:) (L1, R1), M1 (M1), K1 (K1), Generic)
import GHC.Generics qualified as Generics
import Data.Coerce (coerce, Coercible)
import Data.Kind (Type, Constraint)
type GenericCoerce :: (Type -> Type) -> (Type -> Type) -> Constraint
class GenericCoerce a b where
gfrom :: a i -> b i
gto :: b i -> a i
-- unit type data
instance GenericCoerce U1 U1 where
gfrom :: U1 i -> U1 i
gfrom = id
gto :: U1 i -> U1 i
gto = id
-- product type combinations
instance (GenericCoerce a c, GenericCoerce b d) => GenericCoerce (a :*: b) (c :*: d) where
gfrom :: (:*:) a b i -> (:*:) c d i
gfrom (a :*: b) = gfrom a :*: gfrom b
gto :: (:*:) c d i -> (:*:) a b i
gto (a :*: b) = gto a :*: gto b
-- sum type options
instance (GenericCoerce a c, GenericCoerce b d) => GenericCoerce (a :+: b) (c :+: d) where
gfrom :: (:+:) a b i -> (:+:) c d i
gfrom (L1 a) = L1 $ gfrom a
gfrom (R1 b) = R1 $ gfrom b
gto :: (:+:) c d i -> (:+:) a b i
gto (L1 a) = L1 $ gto a
gto (R1 b) = R1 $ gto b
-- types and constructors
instance GenericCoerce a a' => GenericCoerce (M1 i_ c a) (M1 i_' c' a') where
gfrom :: M1 i_ c a i -> M1 i_' c' a' i
gfrom (M1 x) = M1 $ gfrom x
gto :: M1 i_' c' a' i -> M1 i_ c a i
gto (M1 x) = M1 $ gto x
-- constants and parameters
instance Coercible a a' => GenericCoerce (K1 i_ a) (K1 i_' a') where
gfrom :: K1 i_ a i -> K1 i_' a' i
gfrom (K1 x) = K1 $ coerce x
gto :: K1 i_' a' i -> K1 i_ a i
gto (K1 x) = K1 $ coerce x
-- convenience functions
genericCoerce :: (Generic a, Generic b, GenericCoerce (Generics.Rep a) (Generics.Rep b)) => a -> b
genericCoerce = Generics.to . gfrom . Generics.from

View file

@ -0,0 +1,45 @@
{-# LANGUAGE StandaloneKindSignatures #-}
{-# LANGUAGE RoleAnnotations #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# OPTIONS_GHC -Wno-unsafe #-}
{-# OPTIONS_GHC -Wno-missing-safe-haskell-mode #-}
{-# OPTIONS_GHC -Wno-unused-top-binds #-}
module GHC.Generics.Coerce.Example
()
where
import Prelude (Show)
import GHC.Generics (Generic)
import GHC.Generics.Coerce (genericCoerce)
import Data.Int (Int)
import Data.Kind (Type)
type Pair :: Type -> Type -> Type
type role Pair representational representational
data Pair a b = Pair a b
deriving stock (Generic, Show)
tupleCoerce :: Pair a b -> (a, b)
tupleCoerce = genericCoerce
-- >>> tupleCoerce (Pair 1 1)
-- (1,1)
type IntPair :: Type
data IntPair = IntPair Int Int
deriving stock (Generic, Show)
intTupleCoerce :: IntPair -> Pair Int Int
intTupleCoerce = genericCoerce
-- >>> intTupleCoerce (IntPair 1 2)
-- Pair 1 2

View file

@ -0,0 +1,70 @@
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE RoleAnnotations #-}
{-# LANGUAGE StandaloneKindSignatures #-}
{-# LANGUAGE InstanceSigs #-}
{-# OPTIONS_GHC -Wno-unsafe #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE ImportQualifiedPost #-}
module GHC.Generics.CoerceTo
(GenericCoerceTo(..))
where
import Prelude ((.), ($))
import GHC.Generics (Generic(Rep))
import GHC.Generics.Coerce (GenericCoerce())
import GHC.Generics qualified as Generics
import GHC.Generics.Coerce qualified as GenericCoerce
import Data.Kind (Type)
import Data.List qualified as List
import Data.List.NonEmpty (NonEmpty)
import Data.List.NonEmpty qualified as NonEmpty
import Data.Semigroup (Semigroup ((<>), sconcat))
import Data.Monoid (Monoid (mempty, mconcat))
type role GenericCoerceTo representational phantom
type GenericCoerceTo :: Type -> Type -> Type
newtype GenericCoerceTo self other = GenericCoerceTo { get :: self }
toOther :: (Generic b, Generic a, GenericCoerce (Rep a) (Rep b)) => GenericCoerceTo a b -> b
toOther = Generics.to . GenericCoerce.gfrom . Generics.from . get
fromOther :: (Generic a, Generic b, GenericCoerce (Rep a) (Rep b)) => b -> GenericCoerceTo a b
fromOther = GenericCoerceTo . Generics.to . GenericCoerce.gto . Generics.from
instance
(Generic this
, Generic other
, GenericCoerce (Rep this) (Rep other)
, Semigroup other)
=> Semigroup (GenericCoerceTo this other) where
(<>) :: GenericCoerceTo this other -> GenericCoerceTo this other -> GenericCoerceTo this other
lhs <> rhs = fromOther $ toOther lhs <> toOther rhs
sconcat :: NonEmpty (GenericCoerceTo this other) -> GenericCoerceTo this other
sconcat = fromOther . sconcat . NonEmpty.map toOther
instance
(Generic this
, Generic other
, GenericCoerce (Rep this) (Rep other)
, Monoid other)
=> Monoid (GenericCoerceTo this other) where
mempty :: GenericCoerceTo this other
mempty = fromOther mempty
mconcat :: [GenericCoerceTo this other] -> GenericCoerceTo this other
mconcat = fromOther . mconcat . List.map toOther

View file

@ -0,0 +1,32 @@
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_GHC -Wno-unsafe #-}
{-# LANGUAGE StandaloneKindSignatures #-}
module GHC.Generics.CoerceTo.Example () where
import Prelude ()
import GHC.Generics (Generic)
import GHC.Generics.CoerceTo ( GenericCoerceTo(GenericCoerceTo) )
import Data.Kind (Type)
import Data.Semigroup (Semigroup)
import Data.Monoid (Sum(Sum))
import Data.Int (Int)
import Text.Show (Show)
type IntPair :: Type
data IntPair = IntPair Int Int
deriving stock (Generic, Show)
deriving (Semigroup) via (IntPair `GenericCoerceTo` (Sum Int, Sum Int))
-- >>> IntPair 1 1 <> IntPair 1 1
-- IntPair 2 2