
On Wed, Nov 22, 2023 at 12:48:52PM +1030, Darryn wrote:
Thank you to anyone in advance who can help; I do really appreciate it.
I think a simple redefinition of "Formable" takes care of the described obstacle. Do you have other requirements that make it impractical? -- Viktor. --------- {-# LANGUAGE TypeFamilies, TypeFamilyDependencies, MultiParamTypeClasses, FlexibleInstances #-} import Data.Kind (Type) -- A simplified model for sentences. data S a = SA a (S a) | SB a (S a) | SC String deriving (Eq, Show) -- A simplified model for what will be abstract case analysis: data Form a b = FA a b | FB deriving (Eq, Show) -- A simplified a model for the case analysis class: class Formable b where type Aof b :: Type f1 :: b -> Form (Aof b) b f2 :: b -> b f3 :: b -> Bool -- Simple test instance of Formable for S: instance Formable (S a) where type Aof (S a) = a f1 (SA a y) = FA a y f1 (SB a y) = FA a y f1 (SC x) = FB f2 (SA a y) = SA a y f2 (SB a y) = SA a y f2 (SC x) = SC "nothing" f3 (SA a y) = False f3 (SB a y) = False f3 (SC _) = True -- Some test instances all work fine: -- > f1 (SA "a" (SB "b" (SC "c"))) -- > f2 (SA "a" (SB "b" (SC "c"))) -- > f3 (SA "a" (SB "b" (SC "c"))) -- A model of a wrapper for sentences to iadd integer labels: data W a = W Int (S a) deriving (Eq, Show) -- Test instance modelling an instance for labelled sentences: instance Formable (W a) where type Aof (W a) = a f1 (W k (SA a y)) = FA a (W k y) f1 (W k (SB a y)) = FA a (W k y) f1 (W k (SC x)) = FB f2 (W k x) = W (1+k) x f3 (W k (SA a y)) = False f3 (W k (SB a y)) = False f3 (W k (SC _)) = True -- Intend to re-implement f1,f2,f3 in terms of the instance for S once -- I can convince GHC to let both instances stand.