3

私はCourseraのAI計画コースのためにHaskellでAIGeneralProblem Solverをプログラミングしていますが、ghciは型変数があいまいであると不平を言っています。Haskellのコードと私が得るエラーは次のとおりです。

-- Solver.hs
{-# LANGUAGE GADTs,FlexibleInstances,UndecidableInstances,ScopedTypeVariables,TypeFamilies,MultiParamTypeClasses #-}

module Solver
(Solver,State,Transition)
where

class (Show t,Eq t) => Transition t where
 transition :: State s => s -> t -> s

class (Show s,Eq s) => State s where
 getPossibleTransitions :: Transition t => s -> [t]
 isStateValid :: s -> Bool
 isGoalState :: s -> Bool

class Solver s t where
 getPossibleNextStates :: s -> [s]
 isStateVisited :: [s] -> s -> Bool
 getNextFringeStates :: [s] -> [[s]]
 --getNextGeneration :: [s] -> [s] -> [s]

flatten :: [[a]] -> [a]
flatten [] = []
flatten listOfLists = (head listOfLists) ++ (flatten (tail listOfLists))

instance (State s,Transition t) => Solver s t where

 getPossibleNextStates (state::s) =
  filter isStateValid (map transitionFunction possibleTransitions)
  where
   transitionFunction = (transition state)::(t -> s)
   possibleTransitions = (getPossibleTransitions state)::([t])

 isStateVisited visitedStates state =
  any (== state) visitedStates

 getNextFringeStates (states::[s]) =
  map (getPossibleNextStates :: (s -> [s])) (states::[s])

-- COMPILATION:
{-
Prelude> :l Solver.hs
[1 of 1] Compiling Solver           ( Solver.hs, interpreted )

Solver.hs:38:8:
    Ambiguous type variable `t0' in the constraint:
      (Transition t0) arising from a use of `getPossibleNextStates'
    Probable fix: add a type signature that fixes these type variable(s)
    In the first argument of `map', namely
      `(getPossibleNextStates :: s -> [s])'
    In the expression:
      map (getPossibleNextStates :: s -> [s]) (states :: [s])
    In an equation for `getNextFringeStates':
        getNextFringeStates (states :: [s])
          = map (getPossibleNextStates :: s -> [s]) (states :: [s])
Failed, modules loaded: none.
-}
4

2 に答える 2

14

型クラス炎の例があると思います。つまり、実際には何も実行しない型クラスが多すぎるため、推論が難しい複雑なコードになります。

それを診断するのに役立つ型クラス炎の象徴は、ものを機能させるために新しい言語機能を導入し続ける必要があるということです。このルートを進み続けると、後で、実際にはデータを保持せず、さまざまなタイプクラスのインスタンスにするためだけに存在する「ダミータイプ」をたくさん作成する必要があることに気付くでしょう。

LukePalmerとGabrielGonzalezによるこれらのブログ投稿で型クラス炎についてもっと読むことができます(LPのものはより穏やかで、GGのものはもう1つ...極端です)

より良い解決策は、関数もデータであることを覚えておくことです。必要な関数をレコードにまとめて、代わりにレコードを渡すことができます。たとえば、あなたの場合、私はおそらくそれを次のように構成します:

module Solver where

data State s t = State { state :: s
                       , getPossibleTransitions :: [t]
                       , isValid :: Bool
                       , isGoal :: Bool
                       , transition :: t -> State s t }

getPossibleNextStates :: State s t -> [State s t]
getPossibleNextStates s = filter isValid (map transitionFunction possibleTransitions)
    where
        transitionFunction  = transition s
        possibleTransitions = getPossibleTransitions s

isStateVisited :: Eq s => [s] -> State s t -> Bool
isStateVisited visitedStates s = any (== state s) visitedStates

getNextFringeStates :: [State s t] -> [[State s t]]
getNextFringeStates states = map getPossibleNextStates states

特別な言語機能を導入する必要がないことに注意してください。すべての型署名を含めたにもかかわらず、コードもはるかに短くなっています。38行ではなく19行です。

幸運を!

于 2013-02-13T11:17:04.967 に答える
1

Eric Kow は、機能依存関係を使用して私の問題を修正しました。私が要求したように、彼は型クラスを使い続けています。これが魅力のようにコンパイルされる彼のソリューションです。

http://pastebin.com/tnqW2QGn

解決策を見つけた Haskell facebook グループは次のとおりです。

https://www.facebook.com/groups/programming.haskell/

-- Solver.hs
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses  #-}
{-# LANGUAGE ScopedTypeVariables    #-}

module Solver
    (Solver,State,Transition)
  where

class (Show t,Eq t) => Transition t where
    transition :: State s => s -> t -> s

class (Show s,Eq s) => State s where
    getPossibleTransitions :: Transition t => s -> [t]
    isStateValid :: s -> Bool
    isGoalState  :: s -> Bool

class (State s, Transition t) => Solver s t | s -> t where

    getPossibleNextStates :: s -> [s]
    getPossibleNextStates state =
       filter isStateValid (map transitionFunction possibleTransitions)
      where
       transitionFunction  = transition state :: t -> s
       possibleTransitions = getPossibleTransitions state

    isStateVisited        :: [s] -> s -> Bool
    isStateVisited visitedStates state =
       any (== state) visitedStates

    getNextFringeStates :: [s] -> [[s]]
    getNextFringeStates = map getPossibleNextStates
于 2013-02-13T12:24:00.680 に答える