如何派生涉及类型族的泛型遍历
How to derive generic traversals that involve a type family
配置我们的应用程序时,通常定义该字段的方式是
与字段使用方式相同:
data CfgMyHostName = CfgMyHostName Text
其他时候,它们会有所不同。让我们将其正式化为 typeclass:
data UsagePhase = ConfigTime | RunTime -- Used for promotion to types
class Config (a :: UsagePhase -> *) where
type Phase (p :: UsagePhase) a = r | r -> a
toRunTime :: Phase ConfigTime a -> IO (Phase RunTime a)
data DatabaseConfig (p :: UsagePhase)
instance Config DatabaseConfig where
type Phase ConfigTime DatabaseConfig = ConnectInfo
type Phase RunTime DatabaseConfig = ConnectionPool
toRunTime = connect
典型的服务配置有很多字段,每个类别都有一些。
参数化我们将组合在一起的较小组件
让我们写一次大复合记录,而不是两次(一次
对于配置规范,一次用于运行时数据)。这是
类似于 'Trees that Grow' 论文中的想法:
data UiServerConfig (p :: UsagePhase) = CfgUiServerC {
userDatabase :: Phase p DatabaseConfig
cmsDatabase :: Phase p DatabaseConfig
...
kinesisStream :: Phase p KinesisConfig
myHostName :: CfgMyHostName
myPort :: Int
}
UiServerConfig
是我想要配置的众多此类服务之一,因此它
为此类记录类型派生 Generic
并添加一个
默认 toRunTime
实现到 Config
class。这是哪里
我们卡住了。
给定一个像 data Foo f = Foo { foo :: TypeFn f Int, bar :: String}
这样的参数化类型,
我如何一般地推导出任何类型的遍历,例如 Foo
这会影响
每个 TypeFn
记录字段(递归)?
作为我的困惑的一个例子,我尝试像这样使用 generics-sop:
gToRunTime :: (Generic a, All2 Config xs)
=> Phase ConfigTime xs
-> IO (Phase RunTime xs)
gToRunTime = undefined
这失败了,因为 xs :: [[*]]
,但是 Config
接受了一个种类为 a :: ConfigPhase -> *
的类型参数
如能提供任何有关阅读内容以理清思路的提示,我们将不胜感激。满的
解决方案也是可以接受的:)
编辑: 更新为自动派生 AtoB
class.
这是一个似乎有效的解决方案。
没有 Monad 的通用相位映射
这是预赛:
{-# LANGUAGE DataKinds, DeriveGeneric, FlexibleContexts,
FlexibleInstances, KindSignatures, MultiParamTypeClasses,
StandaloneDeriving, TypeFamilies, TypeFamilyDependencies,
TypeSynonymInstances, UndecidableInstances #-}
{-# OPTIONS_GHC -Wall #-}
import qualified GHC.Generics as GHC
import Generics.SOP
现在,假设我们有一个 Phase
:
data Phase = A | B
和字段的 Selector
:
data Selector = Bar | Baz
认为有一个类型 class 具有 (1) 关联类型族,给出与每个可能阶段的选择器关联的具体字段类型,以及 (2) 用于阶段之间映射的接口:
class IsField (sel :: Selector) where
type Field (p :: Phase) sel = r | r -> sel
fieldAtoB :: Field 'A sel -> Field 'B sel
给定一条包含 Field
s 和非 Field
s
的通用实例的记录
data Foo p = Foo { bar :: Field p 'Bar
, baz :: Field p 'Baz
, num :: Int
} deriving (GHC.Generic)
deriving instance Show (Foo 'A)
deriving instance Show (Foo 'B)
instance Generic (Foo p)
和一个 Foo 'A
值:
foo0 :: Foo 'A
foo0 = Foo (BarA ()) (BazA ()) 1
我们想定义一个通用相位映射 gAtoB
:
foo1 :: Foo 'B
foo1 = gAtoB foo0
使用 IsField
类型 class 中的每场相图 fieldAtoB
。
关键步骤是定义一个单独的类型 class AtoB
专用于 A
到 B
阶段的过渡,以充当通向 IsField
输入 class。此AtoB
类型class将与generics-sop
机器结合使用constrain/match具体阶段A
和B
类型字段和分派到适当的 fieldAtoB
相位映射函数。这是 class:
class AtoB aty bty where
fieldAtoB' :: aty -> bty
幸运的是,可以为 Field
自动派生实例,尽管它需要(主要是无害的)UndecidableInstances
扩展:
instance (IsField sel, Field 'A sel ~ aty, Field 'B sel ~ bty)
=> AtoB aty bty where
fieldAtoB' = fieldAtoB
我们可以为非Field
s定义一个实例:
instance {-# OVERLAPPING #-} AtoB ty ty where
fieldAtoB' = id
注意这里的一个限制——如果你在不同的阶段定义一个具有相同具体类型的 Field
,这个与 fieldAtoB' = id
重叠的实例将被使用并且 fieldAtoB
将被忽略。
现在,对于一个特定的选择器Bar
,其基础类型在各自的阶段应该是BarA
和BarB
,我们可以定义下面的IsField
实例:
-- Bar field
data BarA = BarA () deriving (Show) -- Field 'A 'Bar
data BarB = BarB () deriving (Show) -- Field 'B 'Bar
instance IsField 'Bar where
type Field 'A 'Bar = BarA -- defines the per-phase field types for 'Bar
type Field 'B 'Bar = BarB
fieldAtoB (BarA ()) = (BarB ()) -- defines the field phase map
我们可以为Baz
提供类似的定义:
-- Baz field
data BazA = BazA () deriving (Show)
data BazB = BazB () deriving (Show)
instance IsField 'Baz where
type Field 'A 'Baz = BazA
type Field 'B 'Baz = BazB
fieldAtoB (BazA ()) = (BazB ())
现在,我们可以像这样定义通用 gAtoB
转换:
gAtoB :: (Generic (rcrd 'A), Code (rcrd 'A) ~ xssA,
Generic (rcrd 'B), Code (rcrd 'B) ~ xssB,
AllZip2 AtoB xssA xssB)
=> rcrd 'A -> rcrd 'B
gAtoB = to . gAtoBS . from
where
gAtoBS :: (AllZip2 AtoB xssA xssB) => SOP I xssA -> SOP I xssB
gAtoBS (SOP (Z xs)) = SOP (Z (gAtoBP xs))
gAtoBS (SOP (S _)) = error "not implemented"
gAtoBP :: (AllZip AtoB xsA xsB) => NP I xsA -> NP I xsB
gAtoBP Nil = Nil
gAtoBP (I x :* xs) = I (fieldAtoB' x) :* gAtoBP xs
可能有一种方法可以使用 generics-sop
组合器而不是这个明确的定义来做到这一点,但我想不通。
无论如何,gAtoB
对 Foo
记录起作用,根据上面 foo1
的定义,但它也对 Quux
记录起作用:
data Quux p = Quux { bar2 :: Field p 'Bar
, num2 :: Int
} deriving (GHC.Generic)
deriving instance Show (Quux 'A)
deriving instance Show (Quux 'B)
instance Generic (Quux p)
quux0 :: Quux 'A
quux0 = Quux (BarA ()) 2
quux1 :: Quux 'B
quux1 = gAtoB quux0
main :: IO ()
main = do
print foo0
print foo1
print quux0
print quux1
请注意,我使用了具有 Selector
数据类型的选择器,但您可以重写它以使用 (a :: Phase -> *)
类型的选择器,就像我在最后的示例中所做的那样。
Monad 的通用阶段遍历
现在,您需要在 IO
monad 上发生这种情况。这是一个修改后的版本:
{-# LANGUAGE DataKinds, DeriveGeneric, FlexibleContexts,
FlexibleInstances, KindSignatures, MultiParamTypeClasses,
StandaloneDeriving, TypeFamilies, TypeFamilyDependencies,
TypeSynonymInstances, UndecidableInstances #-}
{-# OPTIONS_GHC -Wall #-}
import qualified GHC.Generics as GHC
import Generics.SOP
import Control.Applicative
data Phase = A | B
data Selector = Bar | Baz
class IsField (sel :: Selector) where
type Field (p :: Phase) sel = r | r -> sel
fieldAtoB :: Field 'A sel -> IO (Field 'B sel)
data Foo p = Foo { bar :: Field p 'Bar
, baz :: Field p 'Baz
, num :: Int
} deriving (GHC.Generic)
deriving instance Show (Foo 'A)
deriving instance Show (Foo 'B)
instance Generic (Foo p)
foo0 :: Foo 'A
foo0 = Foo (BarA ()) (BazA ()) 1
foo1 :: IO (Foo 'B)
foo1 = gAtoB foo0
-- fieldAtoB :: Field 'A sel -> Field 'B sel
class AtoB aty bty where
fieldAtoB' :: aty -> IO bty
instance (IsField sel, Field 'A sel ~ aty, Field 'B sel ~ bty) => AtoB aty bty where
fieldAtoB' = fieldAtoB
instance {-# OVERLAPPING #-} AtoB ty ty where
fieldAtoB' = return
-- Bar field
data BarA = BarA () deriving (Show) -- Field 'A 'Bar
data BarB = BarB () deriving (Show) -- Field 'B 'Bar
instance IsField 'Bar where -- defines the per-phase field types for 'Bar
type Field 'A 'Bar = BarA
type Field 'B 'Bar = BarB
fieldAtoB (BarA ()) = return (BarB ()) -- defines the field phase map
-- Baz field
data BazA = BazA () deriving (Show)
data BazB = BazB () deriving (Show)
instance IsField 'Baz where
type Field 'A 'Baz = BazA
type Field 'B 'Baz = BazB
fieldAtoB (BazA ()) = return (BazB ())
gAtoB :: (Generic (rcrd 'A), Code (rcrd 'A) ~ xssA,
Generic (rcrd 'B), Code (rcrd 'B) ~ xssB,
AllZip2 AtoB xssA xssB)
=> rcrd 'A -> IO (rcrd 'B)
gAtoB r = to <$> (gAtoBS (from r))
where
gAtoBS :: (AllZip2 AtoB xssA xssB) => SOP I xssA -> IO (SOP I xssB)
gAtoBS (SOP (Z xs)) = SOP . Z <$> gAtoBP xs
gAtoBS (SOP (S _)) = error "not implemented"
gAtoBP :: (AllZip AtoB xsA xsB) => NP I xsA -> IO (NP I xsB)
gAtoBP Nil = return Nil
gAtoBP (I x :* xs) = I <$> fieldAtoB' x <**> pure (:*) <*> gAtoBP xs
data Quux p = Quux { bar2 :: Field p 'Bar
, num2 :: Int
} deriving (GHC.Generic)
deriving instance Show (Quux 'A)
deriving instance Show (Quux 'B)
instance Generic (Quux p)
quux0 :: Quux 'A
quux0 = Quux (BarA ()) 2
quux1 :: IO (Quux 'B)
quux1 = gAtoB quux0
main :: IO ()
main = do
print foo0
foo1val <- foo1
print foo1val
print quux0
quux1val <- quux1
print quux1val
适应您的问题
这里有一个重写的版本,以尽可能接近您的原始设计。同样,一个关键的限制是具有相同配置时间和 运行 时间类型的 Config
将使用 toRunTime' = return
而不是在其 Config
实例中给出的任何其他定义。
{-# LANGUAGE DataKinds, DeriveGeneric, FlexibleContexts,
FlexibleInstances, KindSignatures, MultiParamTypeClasses,
StandaloneDeriving, TypeFamilies, TypeFamilyDependencies,
TypeSynonymInstances, UndecidableInstances #-}
{-# OPTIONS_GHC -Wall #-}
import qualified GHC.Generics as GHC
import Generics.SOP
import Control.Applicative
data UsagePhase = ConfigTime | RunTime
class Config (sel :: UsagePhase -> *) where
type Phase (p :: UsagePhase) sel = r | r -> sel
toRunTime :: Phase 'ConfigTime sel -> IO (Phase 'RunTime sel)
class ConfigRun cty rty where
toRunTime' :: cty -> IO rty
instance (Config (sel :: UsagePhase -> *),
Phase 'ConfigTime sel ~ cty,
Phase 'RunTime sel ~ rty) => ConfigRun cty rty where
toRunTime' = toRunTime
instance {-# OVERLAPPING #-} ConfigRun ty ty where
toRunTime' = return
-- DatabaseConfig field
data DatabaseConfig (p :: UsagePhase)
data ConnectInfo = ConnectInfo () deriving (Show)
data ConnectionPool = ConnectionPool () deriving (Show)
instance Config DatabaseConfig where
type Phase 'ConfigTime DatabaseConfig = ConnectInfo
type Phase 'RunTime DatabaseConfig = ConnectionPool
toRunTime (ConnectInfo ()) = return (ConnectionPool ())
-- KinesisConfig field
data KinesisConfig (p :: UsagePhase)
data KinesisInfo = KinesisInfo () deriving (Show)
data KinesisStream = KinesisStream () deriving (Show)
instance Config KinesisConfig where
type Phase 'ConfigTime KinesisConfig = KinesisInfo
type Phase 'RunTime KinesisConfig = KinesisStream
toRunTime (KinesisInfo ()) = return (KinesisStream ())
-- CfgMyHostName field
data CfgMyHostName = CfgMyHostName String deriving (Show)
data UiServerConfig (p :: UsagePhase) = CfgUiServerC
{ userDatabase :: Phase p DatabaseConfig
, cmsDatabase :: Phase p DatabaseConfig
, kinesisStream :: Phase p KinesisConfig
, myHostName :: CfgMyHostName
, myPort :: Int
} deriving (GHC.Generic)
deriving instance Show (UiServerConfig 'ConfigTime)
deriving instance Show (UiServerConfig 'RunTime)
instance Generic (UiServerConfig p)
gToRunTime :: (Generic (rcrd 'ConfigTime), Code (rcrd 'ConfigTime) ~ xssA,
Generic (rcrd 'RunTime), Code (rcrd 'RunTime) ~ xssB,
AllZip2 ConfigRun xssA xssB)
=> rcrd 'ConfigTime -> IO (rcrd 'RunTime)
gToRunTime r = to <$> (gToRunTimeS (from r))
where
gToRunTimeS :: (AllZip2 ConfigRun xssA xssB) => SOP I xssA -> IO (SOP I xssB)
gToRunTimeS (SOP (Z xs)) = SOP . Z <$> gToRunTimeP xs
gToRunTimeS (SOP (S _)) = error "not implemented"
gToRunTimeP :: (AllZip ConfigRun xsA xsB) => NP I xsA -> IO (NP I xsB)
gToRunTimeP Nil = return Nil
gToRunTimeP (I x :* xs) = I <$> toRunTime' x <**> pure (:*) <*> gToRunTimeP xs
cfg0 :: UiServerConfig 'ConfigTime
cfg0 = CfgUiServerC (ConnectInfo ()) (ConnectInfo ()) (KinesisInfo())
(CfgMyHostName "localhost") 10
main :: IO ()
main = do
print cfg0
run0 <- gToRunTime cfg0
print run0
配置我们的应用程序时,通常定义该字段的方式是 与字段使用方式相同:
data CfgMyHostName = CfgMyHostName Text
其他时候,它们会有所不同。让我们将其正式化为 typeclass:
data UsagePhase = ConfigTime | RunTime -- Used for promotion to types
class Config (a :: UsagePhase -> *) where
type Phase (p :: UsagePhase) a = r | r -> a
toRunTime :: Phase ConfigTime a -> IO (Phase RunTime a)
data DatabaseConfig (p :: UsagePhase)
instance Config DatabaseConfig where
type Phase ConfigTime DatabaseConfig = ConnectInfo
type Phase RunTime DatabaseConfig = ConnectionPool
toRunTime = connect
典型的服务配置有很多字段,每个类别都有一些。 参数化我们将组合在一起的较小组件 让我们写一次大复合记录,而不是两次(一次 对于配置规范,一次用于运行时数据)。这是 类似于 'Trees that Grow' 论文中的想法:
data UiServerConfig (p :: UsagePhase) = CfgUiServerC {
userDatabase :: Phase p DatabaseConfig
cmsDatabase :: Phase p DatabaseConfig
...
kinesisStream :: Phase p KinesisConfig
myHostName :: CfgMyHostName
myPort :: Int
}
UiServerConfig
是我想要配置的众多此类服务之一,因此它
为此类记录类型派生 Generic
并添加一个
默认 toRunTime
实现到 Config
class。这是哪里
我们卡住了。
给定一个像 data Foo f = Foo { foo :: TypeFn f Int, bar :: String}
这样的参数化类型,
我如何一般地推导出任何类型的遍历,例如 Foo
这会影响
每个 TypeFn
记录字段(递归)?
作为我的困惑的一个例子,我尝试像这样使用 generics-sop:
gToRunTime :: (Generic a, All2 Config xs)
=> Phase ConfigTime xs
-> IO (Phase RunTime xs)
gToRunTime = undefined
这失败了,因为 xs :: [[*]]
,但是 Config
接受了一个种类为 a :: ConfigPhase -> *
如能提供任何有关阅读内容以理清思路的提示,我们将不胜感激。满的 解决方案也是可以接受的:)
编辑: 更新为自动派生 AtoB
class.
这是一个似乎有效的解决方案。
没有 Monad 的通用相位映射
这是预赛:
{-# LANGUAGE DataKinds, DeriveGeneric, FlexibleContexts,
FlexibleInstances, KindSignatures, MultiParamTypeClasses,
StandaloneDeriving, TypeFamilies, TypeFamilyDependencies,
TypeSynonymInstances, UndecidableInstances #-}
{-# OPTIONS_GHC -Wall #-}
import qualified GHC.Generics as GHC
import Generics.SOP
现在,假设我们有一个 Phase
:
data Phase = A | B
和字段的 Selector
:
data Selector = Bar | Baz
认为有一个类型 class 具有 (1) 关联类型族,给出与每个可能阶段的选择器关联的具体字段类型,以及 (2) 用于阶段之间映射的接口:
class IsField (sel :: Selector) where
type Field (p :: Phase) sel = r | r -> sel
fieldAtoB :: Field 'A sel -> Field 'B sel
给定一条包含 Field
s 和非 Field
s
data Foo p = Foo { bar :: Field p 'Bar
, baz :: Field p 'Baz
, num :: Int
} deriving (GHC.Generic)
deriving instance Show (Foo 'A)
deriving instance Show (Foo 'B)
instance Generic (Foo p)
和一个 Foo 'A
值:
foo0 :: Foo 'A
foo0 = Foo (BarA ()) (BazA ()) 1
我们想定义一个通用相位映射 gAtoB
:
foo1 :: Foo 'B
foo1 = gAtoB foo0
使用 IsField
类型 class 中的每场相图 fieldAtoB
。
关键步骤是定义一个单独的类型 class AtoB
专用于 A
到 B
阶段的过渡,以充当通向 IsField
输入 class。此AtoB
类型class将与generics-sop
机器结合使用constrain/match具体阶段A
和B
类型字段和分派到适当的 fieldAtoB
相位映射函数。这是 class:
class AtoB aty bty where
fieldAtoB' :: aty -> bty
幸运的是,可以为 Field
自动派生实例,尽管它需要(主要是无害的)UndecidableInstances
扩展:
instance (IsField sel, Field 'A sel ~ aty, Field 'B sel ~ bty)
=> AtoB aty bty where
fieldAtoB' = fieldAtoB
我们可以为非Field
s定义一个实例:
instance {-# OVERLAPPING #-} AtoB ty ty where
fieldAtoB' = id
注意这里的一个限制——如果你在不同的阶段定义一个具有相同具体类型的 Field
,这个与 fieldAtoB' = id
重叠的实例将被使用并且 fieldAtoB
将被忽略。
现在,对于一个特定的选择器Bar
,其基础类型在各自的阶段应该是BarA
和BarB
,我们可以定义下面的IsField
实例:
-- Bar field
data BarA = BarA () deriving (Show) -- Field 'A 'Bar
data BarB = BarB () deriving (Show) -- Field 'B 'Bar
instance IsField 'Bar where
type Field 'A 'Bar = BarA -- defines the per-phase field types for 'Bar
type Field 'B 'Bar = BarB
fieldAtoB (BarA ()) = (BarB ()) -- defines the field phase map
我们可以为Baz
提供类似的定义:
-- Baz field
data BazA = BazA () deriving (Show)
data BazB = BazB () deriving (Show)
instance IsField 'Baz where
type Field 'A 'Baz = BazA
type Field 'B 'Baz = BazB
fieldAtoB (BazA ()) = (BazB ())
现在,我们可以像这样定义通用 gAtoB
转换:
gAtoB :: (Generic (rcrd 'A), Code (rcrd 'A) ~ xssA,
Generic (rcrd 'B), Code (rcrd 'B) ~ xssB,
AllZip2 AtoB xssA xssB)
=> rcrd 'A -> rcrd 'B
gAtoB = to . gAtoBS . from
where
gAtoBS :: (AllZip2 AtoB xssA xssB) => SOP I xssA -> SOP I xssB
gAtoBS (SOP (Z xs)) = SOP (Z (gAtoBP xs))
gAtoBS (SOP (S _)) = error "not implemented"
gAtoBP :: (AllZip AtoB xsA xsB) => NP I xsA -> NP I xsB
gAtoBP Nil = Nil
gAtoBP (I x :* xs) = I (fieldAtoB' x) :* gAtoBP xs
可能有一种方法可以使用 generics-sop
组合器而不是这个明确的定义来做到这一点,但我想不通。
无论如何,gAtoB
对 Foo
记录起作用,根据上面 foo1
的定义,但它也对 Quux
记录起作用:
data Quux p = Quux { bar2 :: Field p 'Bar
, num2 :: Int
} deriving (GHC.Generic)
deriving instance Show (Quux 'A)
deriving instance Show (Quux 'B)
instance Generic (Quux p)
quux0 :: Quux 'A
quux0 = Quux (BarA ()) 2
quux1 :: Quux 'B
quux1 = gAtoB quux0
main :: IO ()
main = do
print foo0
print foo1
print quux0
print quux1
请注意,我使用了具有 Selector
数据类型的选择器,但您可以重写它以使用 (a :: Phase -> *)
类型的选择器,就像我在最后的示例中所做的那样。
Monad 的通用阶段遍历
现在,您需要在 IO
monad 上发生这种情况。这是一个修改后的版本:
{-# LANGUAGE DataKinds, DeriveGeneric, FlexibleContexts,
FlexibleInstances, KindSignatures, MultiParamTypeClasses,
StandaloneDeriving, TypeFamilies, TypeFamilyDependencies,
TypeSynonymInstances, UndecidableInstances #-}
{-# OPTIONS_GHC -Wall #-}
import qualified GHC.Generics as GHC
import Generics.SOP
import Control.Applicative
data Phase = A | B
data Selector = Bar | Baz
class IsField (sel :: Selector) where
type Field (p :: Phase) sel = r | r -> sel
fieldAtoB :: Field 'A sel -> IO (Field 'B sel)
data Foo p = Foo { bar :: Field p 'Bar
, baz :: Field p 'Baz
, num :: Int
} deriving (GHC.Generic)
deriving instance Show (Foo 'A)
deriving instance Show (Foo 'B)
instance Generic (Foo p)
foo0 :: Foo 'A
foo0 = Foo (BarA ()) (BazA ()) 1
foo1 :: IO (Foo 'B)
foo1 = gAtoB foo0
-- fieldAtoB :: Field 'A sel -> Field 'B sel
class AtoB aty bty where
fieldAtoB' :: aty -> IO bty
instance (IsField sel, Field 'A sel ~ aty, Field 'B sel ~ bty) => AtoB aty bty where
fieldAtoB' = fieldAtoB
instance {-# OVERLAPPING #-} AtoB ty ty where
fieldAtoB' = return
-- Bar field
data BarA = BarA () deriving (Show) -- Field 'A 'Bar
data BarB = BarB () deriving (Show) -- Field 'B 'Bar
instance IsField 'Bar where -- defines the per-phase field types for 'Bar
type Field 'A 'Bar = BarA
type Field 'B 'Bar = BarB
fieldAtoB (BarA ()) = return (BarB ()) -- defines the field phase map
-- Baz field
data BazA = BazA () deriving (Show)
data BazB = BazB () deriving (Show)
instance IsField 'Baz where
type Field 'A 'Baz = BazA
type Field 'B 'Baz = BazB
fieldAtoB (BazA ()) = return (BazB ())
gAtoB :: (Generic (rcrd 'A), Code (rcrd 'A) ~ xssA,
Generic (rcrd 'B), Code (rcrd 'B) ~ xssB,
AllZip2 AtoB xssA xssB)
=> rcrd 'A -> IO (rcrd 'B)
gAtoB r = to <$> (gAtoBS (from r))
where
gAtoBS :: (AllZip2 AtoB xssA xssB) => SOP I xssA -> IO (SOP I xssB)
gAtoBS (SOP (Z xs)) = SOP . Z <$> gAtoBP xs
gAtoBS (SOP (S _)) = error "not implemented"
gAtoBP :: (AllZip AtoB xsA xsB) => NP I xsA -> IO (NP I xsB)
gAtoBP Nil = return Nil
gAtoBP (I x :* xs) = I <$> fieldAtoB' x <**> pure (:*) <*> gAtoBP xs
data Quux p = Quux { bar2 :: Field p 'Bar
, num2 :: Int
} deriving (GHC.Generic)
deriving instance Show (Quux 'A)
deriving instance Show (Quux 'B)
instance Generic (Quux p)
quux0 :: Quux 'A
quux0 = Quux (BarA ()) 2
quux1 :: IO (Quux 'B)
quux1 = gAtoB quux0
main :: IO ()
main = do
print foo0
foo1val <- foo1
print foo1val
print quux0
quux1val <- quux1
print quux1val
适应您的问题
这里有一个重写的版本,以尽可能接近您的原始设计。同样,一个关键的限制是具有相同配置时间和 运行 时间类型的 Config
将使用 toRunTime' = return
而不是在其 Config
实例中给出的任何其他定义。
{-# LANGUAGE DataKinds, DeriveGeneric, FlexibleContexts,
FlexibleInstances, KindSignatures, MultiParamTypeClasses,
StandaloneDeriving, TypeFamilies, TypeFamilyDependencies,
TypeSynonymInstances, UndecidableInstances #-}
{-# OPTIONS_GHC -Wall #-}
import qualified GHC.Generics as GHC
import Generics.SOP
import Control.Applicative
data UsagePhase = ConfigTime | RunTime
class Config (sel :: UsagePhase -> *) where
type Phase (p :: UsagePhase) sel = r | r -> sel
toRunTime :: Phase 'ConfigTime sel -> IO (Phase 'RunTime sel)
class ConfigRun cty rty where
toRunTime' :: cty -> IO rty
instance (Config (sel :: UsagePhase -> *),
Phase 'ConfigTime sel ~ cty,
Phase 'RunTime sel ~ rty) => ConfigRun cty rty where
toRunTime' = toRunTime
instance {-# OVERLAPPING #-} ConfigRun ty ty where
toRunTime' = return
-- DatabaseConfig field
data DatabaseConfig (p :: UsagePhase)
data ConnectInfo = ConnectInfo () deriving (Show)
data ConnectionPool = ConnectionPool () deriving (Show)
instance Config DatabaseConfig where
type Phase 'ConfigTime DatabaseConfig = ConnectInfo
type Phase 'RunTime DatabaseConfig = ConnectionPool
toRunTime (ConnectInfo ()) = return (ConnectionPool ())
-- KinesisConfig field
data KinesisConfig (p :: UsagePhase)
data KinesisInfo = KinesisInfo () deriving (Show)
data KinesisStream = KinesisStream () deriving (Show)
instance Config KinesisConfig where
type Phase 'ConfigTime KinesisConfig = KinesisInfo
type Phase 'RunTime KinesisConfig = KinesisStream
toRunTime (KinesisInfo ()) = return (KinesisStream ())
-- CfgMyHostName field
data CfgMyHostName = CfgMyHostName String deriving (Show)
data UiServerConfig (p :: UsagePhase) = CfgUiServerC
{ userDatabase :: Phase p DatabaseConfig
, cmsDatabase :: Phase p DatabaseConfig
, kinesisStream :: Phase p KinesisConfig
, myHostName :: CfgMyHostName
, myPort :: Int
} deriving (GHC.Generic)
deriving instance Show (UiServerConfig 'ConfigTime)
deriving instance Show (UiServerConfig 'RunTime)
instance Generic (UiServerConfig p)
gToRunTime :: (Generic (rcrd 'ConfigTime), Code (rcrd 'ConfigTime) ~ xssA,
Generic (rcrd 'RunTime), Code (rcrd 'RunTime) ~ xssB,
AllZip2 ConfigRun xssA xssB)
=> rcrd 'ConfigTime -> IO (rcrd 'RunTime)
gToRunTime r = to <$> (gToRunTimeS (from r))
where
gToRunTimeS :: (AllZip2 ConfigRun xssA xssB) => SOP I xssA -> IO (SOP I xssB)
gToRunTimeS (SOP (Z xs)) = SOP . Z <$> gToRunTimeP xs
gToRunTimeS (SOP (S _)) = error "not implemented"
gToRunTimeP :: (AllZip ConfigRun xsA xsB) => NP I xsA -> IO (NP I xsB)
gToRunTimeP Nil = return Nil
gToRunTimeP (I x :* xs) = I <$> toRunTime' x <**> pure (:*) <*> gToRunTimeP xs
cfg0 :: UiServerConfig 'ConfigTime
cfg0 = CfgUiServerC (ConnectInfo ()) (ConnectInfo ()) (KinesisInfo())
(CfgMyHostName "localhost") 10
main :: IO ()
main = do
print cfg0
run0 <- gToRunTime cfg0
print run0