freeおよびcompdataパッケージを使用して、「free monads」と「datatypes a la carte」に基づいて構成可能な DSL をいくつか構築しています ( Combining Free typesの精神に似ています)。
これはいくつかの単純な DSL では機能しますが、この型パラメーターに依存しないコンストラクター/コマンドの場合、型パラメーターを持つものに行き詰まり、GHC からあいまいな型パラメーターエラーが発生します。
明確にするために、ここにいくつかのコードがあります:
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeOperators #-}
module DSL where
import Data.Comp
import Control.Monad.Free
type Index = Int
data DSL a next = Read Index (a -> next)
| Write a (Index -> next)
| GetLastIndex (Index -> next)
deriving (Functor)
read :: (Functor f, DSL a :<: f, MonadFree f m) => Index -> m a
read idx = liftF (inj (Read idx id))
write :: (Functor f, DSL a :<: f, MonadFree f m) => a -> m Index
write a = liftF (inj (Write a id))
-- This works
getLastIndex' :: MonadFree (DSL a) m => m Index
getLastIndex' = liftF (GetLastIndex id)
-- This doesn't:
--
-- Could not deduce (Data.Comp.Ops.Subsume
-- (compdata-0.10:Data.Comp.SubsumeCommon.ComprEmb
-- (Data.Comp.Ops.Elem (DSL a0) f))
-- (DSL a0)
-- f)
-- from the context (Functor f, DSL a :<: f, MonadFree f m)
-- bound by the type signature for
-- getLastIndex :: (Functor f, DSL a :<: f, MonadFree f m) => m Index
-- at simple.hs:30:17-66
-- The type variable ‘a0’ is ambiguous
-- In the ambiguity check for the type signature for ‘getLastIndex’:
-- getLastIndex :: forall (m :: * -> *) (f :: * -> *) a.
-- (Functor f, DSL a :<: f, MonadFree f m) =>
-- m Index
-- To defer the ambiguity check to use sites, enable AllowAmbiguousTypes
-- In the type signature for ‘getLastIndex’:
-- getLastIndex :: (Functor f, DSL a :<: f, MonadFree f m) => m Index
getLastIndex :: (Functor f, DSL a :<: f, MonadFree f m) => m Index
-- getLastIndex = liftF (inj (GetLastIndex id))
getLastIndex = _
GHC で示唆されているように、 AllowAmbiguousTypes拡張機能を有効にしてこれを機能させようとしても、それ以上はうまくいきませんでした。型シグネチャにforall aスタイルのものをいくつか追加しようとしましたが、役に立ちませんでした。
このパターンを機能させる方法はありますか?