4

在配置我们的应用程序时,通常定义字段的方式与使用字段的方式相同:

data CfgMyHostName = CfgMyHostName Text

其他时候,它们有所不同。让我们在类型类中正式化:

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

一个典型的服务配置有很多字段,每个类别都有一些。参数化我们将组合在一起的较小组件让我们编写大型复合记录一次,而不是两次(一次用于配置规范,一次用于运行时数据)。这类似于“生长的树木”论文中的想法:

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。这就是我们卡住的地方。

给定一个参数化的类型 like 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需要一个带有 kind 的类型参数a :: ConfigPhase -> *

任何关于阅读什么以便理清思路的提示都将不胜感激。完整的解决方案也是可以接受的:)

4

1 回答 1

3

编辑:更新为自动派生AtoB类。

这是一个似乎有效的解决方案。

没有 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

想法是有一个类型类,它具有(1)一个关联的类型族,为每个可能的阶段提供与选择器关联的具体字段类型,以及(2)一个用于阶段之间映射的接口:

class IsField (sel :: Selector) where
  type Field (p :: Phase) sel = r | r -> sel
  fieldAtoB :: Field 'A sel -> Field 'B sel

给定一个包含Fields 和非Fields的通用实例的记录

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

它使用类型类中fieldAtoB的每场相位图。IsField

关键步骤是定义一个单独的类型类AtoB,专用于阶段AB过渡,以充当IsField类型类的桥梁。该AtoB类型类将与机器结合使用,以逐个字段generics-sop约束/匹配具体阶段A和类型,并分派到适当的阶段映射函数。这是课程:BfieldAtoB

class AtoB aty bty where
  fieldAtoB' :: aty -> bty

幸运的是,可以为Fields 自动派生实例,尽管它需要(大部分无害的)UndecidableInstances扩展:

instance (IsField sel, Field 'A sel ~ aty, Field 'B sel ~ bty) 
         => AtoB aty bty where
  fieldAtoB' = fieldAtoB

我们可以为非Fields 定义一个实例:

instance {-# OVERLAPPING #-} AtoB ty ty where
  fieldAtoB' = id

请注意这里的一个限制——如果您在不同阶段定义具有相同具体类型的 a,则将使用Field此重叠实例并将其忽略。fieldAtoB' = idfieldAtoB

现在,对于一个特定的选择器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于记录,但它也适用于记录:Foofoo1Quux

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数据类型的选择器,但是您可以将其重写为使用 type 的选择器(a :: Phase -> *),就像我在最后的示例中所做的那样。

Monad 上的通用阶段遍历

现在,您需要在IOmonad 上发生这种情况。这是一个修改后的版本:

{-# 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使用具有相同配置时间和运行时间类型的a,而不是在其实例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
于 2018-07-18T19:11:53.150 回答