2
get
이라는 메서드가 들어있는 Generic
클래스에 데이터 형식 제네릭 프로그래밍을 사용하고 있습니다. 내 최종 사용자가 유형을 정의하고 deriving Generic
을 추가 잊어 및 put
를 호출하면, 그들은 이와 같은 오류 메시지가 표시됩니다 :데이터 유형 - 제네릭 프로그래밍과 신비한 gdmXXX
No instance for (ALife.Creatur.Genetics.Code.BRGCWord8.GGene
(GHC.Generics.Rep ClassifierGene))
arising from a use of `ALife.Creatur.Genetics.Code.BRGCWord8.$gdmput'
나는 어떻게 오류를 수정하는 사용자를 알 수 있습니다,하지만 난이 궁금합니다 $gdmput
. 나는 그것이 자동으로 생성 된 함수 또는 심볼이라고 가정하지만, 무엇에 의해? DefaultSignatures
pragma 또는 DeriveGeneric
pragma를 사용하고 있습니까? 데이터 유형 - 제네릭 프로그래밍에 대한 몇 가지 문서를 읽었지만 gdmXXX
심볼에 대한 참조를 찾지 못했습니다.
다음은 Generic
클래스의 정의입니다.
{-# LANGUAGE TypeFamilies, FlexibleContexts, FlexibleInstances,
DefaultSignatures, DeriveGeneric, TypeOperators #-}
. . .
-- | A class representing anything which is represented in, and
-- determined by, an agent's genome.
-- This might include traits, parameters, "organs" (components of
-- agents), or even entire agents.
-- Instances of this class can be thought of as genes, i.e.,
-- instructions for building an agent.
class Genetic g where
-- | Writes a gene to a sequence.
put :: g -> Writer()
default put :: (Generic g, GGenetic (Rep g)) => g -> Writer()
put = gput . from
-- | Reads the next gene in a sequence.
get :: Reader (Either [String] g)
default get :: (Generic g, GGenetic (Rep g)) => Reader (Either [String] g)
get = do
a <- gget
return $ fmap to a
getWithDefault :: g -> Reader g
getWithDefault d = fmap (fromEither d) get
class GGenetic f where
gput :: f a -> Writer()
gget :: Reader (Either [String] (f a))
-- | Unit: used for constructors without arguments
instance GGenetic U1 where
gput U1 = return()
gget = return (Right U1)
-- | Constants, additional parameters and recursion of kind *
instance (GGenetic a, GGenetic b) => GGenetic (a :*: b) where
gput (a :*: b) = gput a >> gput b
gget = do
a <- gget
b <- gget
return $ (:*:) <$> a <*> b
-- | Meta-information (constructor names, etc.)
instance (GGenetic a, GGenetic b) => GGenetic (a :+: b) where
gput (L1 x) = putRawWord16 0 >> gput x
gput (R1 x) = putRawWord16 1 >> gput x
gget = do
a <- getRawWord16
case a of
Right x -> do
if even x -- Only care about the last bit
then fmap (fmap L1) gget
else fmap (fmap R1) gget
Left s -> return $ Left s
-- | Sums: encode choice between constructors
instance (GGenetic a) => GGenetic (M1 i c a) where
gput (M1 x) = gput x
gget = fmap (fmap M1) gget
-- | Products: encode multiple arguments to constructors
instance (Genetic a) => GGenetic (K1 i a) where
gput (K1 x) = put x
gget = do
a <- get
return $ fmap K1 a