7

Haskell で型付き式パーサーを作成しようとしていますが、これはこれまでのところうまく機能していますが、現在、高階関数の実装に苦労しています。問題を簡単な例に要約しました。

{-# LANGUAGE TypeFamilies,GADTs,FlexibleContexts,RankNTypes #-}

-- A function has an argument type and a result type
class Fun f where
  type FunArg f
  type FunRes f

-- Expressions are either constants of function applications
data Expr a where
  Const :: a -> Expr a
  App :: Fun f => f -> FunArg f -> Expr (FunRes f)

-- A very simple function
data Plus = Plus

-- Which takes two integer expressions and returns an integer expression
instance Fun Plus where
  type FunArg Plus = (Expr Int,Expr Int)
  type FunRes Plus = Int

-- A more complicated function which lifts a function to lists (like in haskell)
data Map f r = Map f

-- For this we need the concept of lifting function arguments:
class Liftable a where
  type LiftRes a

-- A singleton argument is lifted by changing the expression type from a to [a]
instance Liftable (Expr a) where
  type LiftRes (Expr a) = Expr [a]

-- Two function arguments are lifted by lifting each argument
instance (Liftable a,Liftable b) => Liftable (a,b)  where
  type LiftRes (a,b) = (LiftRes a,LiftRes b)

-- Now we can declare a function instance for Map
instance (Fun f,Liftable (FunArg f),r ~ LiftRes (FunArg f)) => Fun (Map f r) where
  type FunArg (Map f r) = r
  type FunRes (Map f r) = [FunRes f]

-- Now a parser for functions:
parseFun :: [String] -> (forall f. Fun f => f -> a) -> a
-- The parser for the plus function is easy:
parseFun ["plus"] f = f Plus
-- But the parser for map is not possible:
parseFun ("map":sym) f 
  = parseFun sym (\fun -> f (Map fun))

問題は、再帰的なクラス宣言が禁止されているため、すべての LiftRes 自体が Liftable であることを型チェッカーに納得させる方法がないことです。

私の質問は次のとおりです。これを機能させるにはどうすればよいですか? ヒントを得ることができる型付き式パーサーの他の例はありますか?

編集:型ファミリの制約に関するこの議論は、非常に関連しているようです。しかし、私の場合、彼らのソリューションを機能させることができませんでした。誰かがそれを手伝ってくれるでしょうか?

4

1 に答える 1

4

サンプルを機能させる最も簡単な方法はLiftable (FunArg f)、インスタンス宣言から制約を削除することです。しかし、あなたの例は非常に凝縮されているため、実際に必要な理由を示していないと思います。

したがって、次善の策は、Liftable (FunArg f)スーパークラスの制約をクラスに追加することですFun

class Liftable (FunArg f) => Fun f where
  ...

これが不可能な場合 (つまり、すべての関数が持ち上げ可能な引数の型を持っていない場合)、指定さparseFunれた型の a を書くことは期待できません。

より一般的な意見: あなたがここでやろうとしていることは非常に奇妙で、おそらく一度にやりすぎだと思います。構造化されていない文字列からコンテキストフリーのデータ型に解析することは、すでに十分に困難です。最初にそれを行い、「型付けされていない」言語の構造化表現を型付き表現に変換する別の関数を作成してください。

EDIT (コメントへの反応として、改訂):質問でリンクしたタイプファミリーの制約に関する議論で指摘されているように、を使用してスーパークラスのサイクル制限をバイパスできますConstraintKinds。縮小した例を機能させる方法を次に示します。おそらく、これは完全なソリューションに拡張されますか?

{-# LANGUAGE RankNTypes, ScopedTypeVariables, TypeFamilies, FlexibleContexts, GADTs #-}

import Data.Constraint  -- from the constraints package
import Data.Proxy       -- from the tagged package

-- A function has an argument type and a result type
class Liftable (FunArg f) => Fun f where
  type FunArg f
  type FunRes f

-- Expr, Plus, and instance Fun Plus as before

class Liftable a where
  type LiftRes a
  get :: p a -> Dict (Liftable (LiftRes a))
    -- acquire "superclass" dictionary by calling this method and
    -- then pattern matching on the result

instance Liftable (Expr a) where
  type LiftRes (Expr a) = Expr [a]
  get _ = Dict

instance (Liftable a, Liftable b) => Liftable (a, b) where
  type LiftRes (a, b) = (LiftRes a, LiftRes b)
  get (_ :: p (a, b)) =
    case get (Proxy :: Proxy a) of -- extra code required
      Dict -> case get (Proxy :: Proxy b) of -- extra code required
        Dict -> Dict

data Map f r = Map f

instance (Fun f, Liftable r, r ~ LiftRes (FunArg f)) => Fun (Map f r) where
  type FunArg (Map f r) = r
  type FunRes (Map f r) = [FunRes f]

parseFun :: forall a. [String] -> (forall f. Fun f => f -> a) -> a
parseFun ["plus"]      f = f Plus
parseFun ("map" : sym) f = parseFun sym
  (\ (fun :: g) -> case get (Proxy :: Proxy (FunArg g)) of -- extra code required
                     Dict -> f (Map fun))
于 2013-02-26T12:44:22.920 に答える