GADT, TypeFamilies type input failure when implementing "mixins"

I am trying to create complex data structures with composite logic. That is, the data structure has a common format (essentially, a record with some fields, the type of which can be changed) and some common functions. Concrete structures have a specific implementation of common functions.

There are two approaches that I have tried. One of them is to use a type system (with class types, type families, functional dependencies, etc.). Another creates my own “virtual table” and uses GADT. Both methods do not work in the same way - it seems that there is something basic that I'm missing here. Or maybe there is an even better way for Haskell-ish to do this?

Here is the unsuccessful "typed" code:

{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeSynonymInstances #-} module Typed where import Control.Monad.State import Data.Lens.Lazy import Data.Lens.Template -- Generic Block. data Block state ports = Block { _blockState :: state, _blockPorts :: ports } -- For the logic we want to use, we need some state and ports. data LogicState = LogicState { _field :: Bool } data LogicPorts incoming outgoing = LogicPorts { _input :: incoming, _output :: outgoing } makeLenses [ ''Block, ''LogicState, ''LogicPorts ] -- We need to describe how to reach the needed state and ports, -- and provide a piece of the logic. class LogicBlock block incoming outgoing | block -> incoming, block -> outgoing where logicState :: block ~ Block state ports => Lens state LogicState logicPorts :: block ~ Block state ports => Lens ports (LogicPorts incoming outgoing) convert :: block ~ Block state ports => incoming -> State block outgoing runLogic :: State block outgoing runLogic = do state <- access $ blockState let myField = state ^. logicState ^. field if myField then do ports <- access blockPorts let inputMessage = ports ^. logicPorts ^. input convert inputMessage else error "Sorry" -- My block uses the generic logic, and also maintains additional state -- and ports. data MyState = MyState { _myLogicState :: LogicState, _myMoreState :: Bool } data MyPorts = MyPorts { _myLogicPorts :: LogicPorts Int Bool, _myMorePorts :: Int } makeLenses [ ''MyState, ''MyPorts ] type MyBlock = Block MyState MyPorts instance LogicBlock MyBlock Int Bool where logicState = myLogicState logicPorts = myLogicPorts convert x = return $ x > 0 -- All this work to write: testMyBlock :: State MyBlock Bool testMyBlock = runLogic 

This results in the following error:

 Typed.hs:39:7: Could not deduce (block ~ Block state1 ports1) from the context (LogicBlock block incoming outgoing) bound by the class declaration for `LogicBlock' at Typed.hs:(27,1)-(41,19) `block' is a rigid type variable bound by the class declaration for `LogicBlock' at Typed.hs:26:18 Expected type: StateT block Data.Functor.Identity.Identity outgoing Actual type: State (Block state1 ports1) outgoing In the return type of a call of `convert' In a stmt of a 'do' block: convert inputMessage 

And here is the failed "vtable" code:

 {-# LANGUAGE GADTs #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TemplateHaskell #-} module VTable where import Control.Monad.State import Data.Lens.Lazy import Data.Lens.Template -- Generic Block. data Block state ports = Block { _blockState :: state, _blockPorts :: ports } -- For the logic we want to use, we need some state and ports. data LogicState = LogicState { _field :: Bool } data LogicPorts incoming outgoing = LogicPorts { _input :: incoming, _output :: outgoing } makeLenses [ ''Block, ''LogicState, ''LogicPorts ] -- We need to describe how to reach the needed state and ports, -- and provide a piece of the logic. data BlockLogic block incoming outgoing where BlockLogic :: { logicState :: Lens state LogicState , logicPorts :: Lens ports (LogicPorts incoming outgoing) , convert :: incoming -> State block outgoing } -> BlockLogic (Block state ports) incoming outgoing -- | The generic piece of logic. runLogic :: forall block state ports incoming outgoing . block ~ Block state ports => BlockLogic block incoming outgoing -> State block outgoing runLogic BlockLogic { .. } = do state <- access $ blockState let myField = state ^. logicState ^. field if myField then do ports <- access blockPorts let inputMessage = ports ^. logicPorts ^. input convert inputMessage else error "Sorry" -- My block uses the generic logic, and also maintains additional state and ports. data MyState = MyState { _myLogicState :: LogicState, _myMoreState :: Bool } data MyPorts = MyPorts { _myLogicPorts :: LogicPorts Int Bool, _myMorePorts :: Int } makeLenses [ ''MyState, ''MyPorts ] type MyBlock = Block MyState MyPorts -- All this work to write: testMyBlock :: State MyBlock Bool testMyBlock = runLogic $ BlockLogic { logicState = myLogicState , logicPorts = myLogicPorts , convert = \x -> return $ x > 0 } 

This results in the following error:

 VTable.hs:44:5: Could not deduce (block1 ~ Block state1 ports1) from the context (block ~ Block state ports) bound by the type signature for runLogic :: block ~ Block state ports => BlockLogic block incoming outgoing -> State block outgoing at VTable.hs:(37,1)-(46,17) or from (block ~ Block state1 ports1) bound by a pattern with constructor BlockLogic :: forall incoming outgoing state ports block. Lens state LogicState -> Lens ports (LogicPorts incoming outgoing) -> (incoming -> State block outgoing) -> BlockLogic (Block state ports) incoming outgoing, in an equation for `runLogic' at VTable.hs:37:10-26 `block1' is a rigid type variable bound by a pattern with constructor BlockLogic :: forall incoming outgoing state ports block. Lens state LogicState -> Lens ports (LogicPorts incoming outgoing) -> (incoming -> State block outgoing) -> BlockLogic (Block state ports) incoming outgoing, in an equation for `runLogic' at VTable.hs:37:10 Expected type: block1 Actual type: block Expected type: StateT block1 Data.Functor.Identity.Identity outgoing Actual type: State block outgoing In the return type of a call of `convert' In a stmt of a 'do' block: convert inputMessage 

I don’t understand why the GHC is going for "block1" when all of this is explicitly specified under ScopedTypeVariables and "forall block".

Edit # 1: Functional dependencies added, thanks to Chris Kuklevich to point this out. The problem remains, though.

Edit # 2: As Chris noted, in VTable's solution, getting rid of all the “block-state blocks of the block” and instead writing “Block port states” solves the problem.

Edit # 3: Good, so the problem is that for each individual function, the GHC requires enough type information in the parameters to output all types, even for types that are not used at all. Thus, in the case of (for example) logicState above, the parameters give us only a state that is not enough to know what the ports are, incoming and outgoing types. It doesn’t matter for the logicState function; GHC wants to know and cannot, so compilation fails. If this is really the main reason, it would be better if the GHC complained directly when compiling the StateState logical statement - it seems to have enough information to detect a problem there; if I saw a problem saying "port type is not used / not defined" in this place, it would be much clearer.

Edit # 4: it's still not clear to me why (block ~ Block state ports) doesn't work; I guess I'm using it for an unintended purpose? Looks like it should work. I agree with Chris that using CPP to work around is an abomination; but writing "B trpe" (in my real code, which has more paranons) is also not a good solution.

+4
source share
1 answer

I have a one line fix for your VTable code:

  , convert :: incoming -> State block outgoing 

becomes

  , convert :: incoming -> State (Block state ports) outgoing 

Then you should simplify the runLogic type to

 runLogic :: BlockLogic (Block state ports) incoming outgoing -> State (Block state ports) outgoing 

PS: more detailed answer to the comments below.

Eliminating "block ~" was not part of the fix. Usually "~" is only required in situations instance a~b => ... where .

Previously, if I give the function a xxx :: BlockLogic (Block state ports) incoming outgoing , then it can unpack convert xxx :: State block outgoing . But the new block is not at all connected with (Block state ports) , it is a new unrecognizable type. The compiler adds a number to the end of the name to make block1 , which then appears in the error messages.

The source code (both versions) has problems with types that the compiler can infer from a given context.

For details, try type . Do not use CPP and DEFINE.

 type B sp = BlockLogic (Block sp) runLogic :: B spio -> State (Block sp) o 

PPS: further explanation of problems with the class version. If I replaced (Block sp) with a block and added the mentioned functional dependencies:

 class LogicBlock state ports incoming outgoing | state ports -> incoming outgoing where logicState :: Lens state LogicState logicPorts :: Lens ports (LogicPorts incoming outgoing) convert :: incoming -> State (Block state ports) outgoing 

Using logicState nails down state , but leaves ports unknown, making ports#

Using logicPorts nails down ports , but leaves state unknown, making ports#

The runLogic compilation runLogic a lot of type mismatch errors between ports, ports 0, ports1 and state, state0, state1.

These operations do not seem to be combined into one class. You can break them into separate classes of classes or, possibly, add functional dependencies ", state-> ports, ports-> state" to the class declaration.

+4
source

All Articles