Skip to content

Instantly share code, notes, and snippets.

@meditans
Created February 23, 2020 11:21
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save meditans/d3b5970d7d1d7cb0f4af98091a41f2c1 to your computer and use it in GitHub Desktop.
Save meditans/d3b5970d7d1d7cb0f4af98091a41f2c1 to your computer and use it in GitHub Desktop.
Another question about generic-data-surgery
{-# LANGUAGE DeriveGeneric, TypeApplications, DataKinds, TypeOperators,
DerivingStrategies, GeneralizedNewtypeDeriving, UndecidableInstances #-}
module Inconsistency where
import Data.Text (Text)
import qualified GHC.Generics as GHC
import Generic.Data.Surgery
import Generic.Data.Surgery.Internal
import Fcf
data Pet = Dog | Horse | Dragon
deriving (Show, Read, Bounded, Enum)
data Person = Person
{ name :: Text
, age :: Int
, pet :: Maybe Pet
} deriving GHC.Generic
-- addKey1 :: Person -> _
-- addKey1 p = fromOR' $ insertRField' @"pk" @0 @Int def $ toOR p
-- if I check the type of the wildcard in this expression ^, GHC tells me that I need:
type PersonWithId =
GHC.M1
GHC.D
('GHC.MetaData "Person" "Inconsistency" "main" 'False)
(GHC.M1
GHC.C
('GHC.MetaCons "Person" 'GHC.PrefixI 'True)
((GHC.M1 GHC.S (DefaultMetaSel ('Just "pk")) (GHC.K1 GHC.R Int)
GHC.:*: GHC.M1
GHC.S
('GHC.MetaSel
('Just "name")
'GHC.NoSourceUnpackedness
'GHC.NoSourceStrictness
'GHC.DecidedLazy)
(GHC.K1 GHC.R Text))
GHC.:*: (GHC.M1
GHC.S
('GHC.MetaSel
('Just "age")
'GHC.NoSourceUnpackedness
'GHC.NoSourceStrictness
'GHC.DecidedLazy)
(GHC.K1 GHC.R Int)
GHC.:*: GHC.M1
GHC.S
('GHC.MetaSel
('Just "pet")
'GHC.NoSourceUnpackedness
'GHC.NoSourceStrictness
'GHC.DecidedLazy)
(GHC.K1 GHC.R (Maybe Pet)))))
-- so that I can say:
addKey2 :: Person -> Data PersonWithId ()
addKey2 p = fromOR' $ insertRField' @"pk" @0 @Int 0 $ toOR p
-- but I can also define
type PersonWithIdSynthetic = Eval (InsertField 0 ('Just "pk") Int (GHC.Rep Person))
newtype Wrapper = Wrapper (Data PersonWithIdSynthetic ())
deriving newtype GHC.Generic
-- BUT, when I try to write:
addKey3 :: Person -> Wrapper
addKey3 p = Wrapper $ fromOR' $ insertRField' @"pk" @0 @Int 0 $ toOR p
-- I get:
-- Inconsistency.hs:74:23-70: error:
-- • Couldn't match type ‘GHC.M1
-- GHC.S
-- ('GHC.MetaSel
-- ('Just "pet")
-- 'GHC.NoSourceUnpackedness
-- 'GHC.NoSourceStrictness
-- 'GHC.DecidedLazy)
-- (GHC.K1 GHC.R (Maybe Pet))’
-- with ‘GHC.S1
-- ('GHC.MetaSel
-- ('Just "age")
-- 'GHC.NoSourceUnpackedness
-- 'GHC.NoSourceStrictness
-- 'GHC.DecidedLazy)
-- (GHC.Rec0 Int)
-- GHC.:*: GHC.S1
-- ('GHC.MetaSel
-- ('Just "pet")
-- 'GHC.NoSourceUnpackedness
-- 'GHC.NoSourceStrictness
-- 'GHC.DecidedLazy)
-- (GHC.Rec0 (Maybe Pet))’
-- arising from a use of ‘fromOR'’
-- • In the second argument of ‘($)’, namely
-- ‘fromOR' $ insertRField' @"pk" @0 @Int 0 $ toOR p’
-- In the expression:
-- Wrapper $ fromOR' $ insertRField' @"pk" @0 @Int 0 $ toOR p
-- In an equation for ‘addKey3’:
-- addKey3 p
-- = Wrapper $ fromOR' $ insertRField' @"pk" @0 @Int 0 $ toOR p
-- |
-- 74 | addKey3 p = Wrapper $ fromOR' $ insertRField' @"pk" @0 @Int 0 $ toOR p
-- | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
-- why are the two types differents?
@meditans
Copy link
Author

@Lysxia any idea?

@Lysxia
Copy link

Lysxia commented Feb 23, 2020

Ah, I forgot that fromOR' and toOR introduce some normalization steps. So the synthetic type should really be

type PersonWithIdSynthetic = Arborify (Eval (InsertField 0 ('Just "pk") Int (Linearize (GHC.Rep Person))))

@Lysxia
Copy link

Lysxia commented Feb 23, 2020

Feel free to open issues on Github about this.

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment