Understanding version differences

The compiler defaults the kind of 'quality' (i.e. the first argument of
QUALITIES) to *, not being able to infer it from the class definition
itself (and other definitions that it references).
Since you want it to have kind * -> *, you should enable KindSignatures
and add an annotation, or otherwise disambiguate the kind.
This behaviour follows the Haskell Report. The change from previous
versions of GHC is documented here:
http://www.haskell.org/ghc/docs/7.4.1/html/users_guide/release-7-4-1.html#id...
Roman
* Patrick Browne
Hi, The code [1] below compiles and runs with GHCi version 7.0.4. I get one warning and an error message with GHCi version 7.6.1. 1) Warning -XDatatypeContexts is deprecated. Unless there are propagation effects, this is well explained. 2) foom-1.hs:65:15: `quality' is applied to too many type arguments In the type `quality entity -> agent -> IO Observation' In the class declaration for `OBSERVERS' Failed, modules loaded: none. I do not understand the error message from 7.6.1. I am not too interested actually fixing it, I just want to understand it. Thanks, Pat [1]The code is from: A Functional Ontology of Observation and Measurement Werner Kuhn {-# LANGUAGE DatatypeContexts,MultiParamTypeClasses #-} module ENDURANTS where import System.Time type Id = String type Position = Integer type Moisture = Float type Celsius = String type Heat = Float data WeatherStation = WeatherStation Id Position deriving Show data Value = Boolean Bool | Count Int | Measure Float | Category String deriving Show data Observation = Observation Value Position ClockTime deriving Show data AmountOfAir = AmountOfAir Heat Moisture deriving Show muensterAir = AmountOfAir 10.0 70.0 class ENDURANTS endurant where
-- must add instances all down the hierarchy for each instance instance ENDURANTS WeatherStation where instance ENDURANTS AmountOfAir where class ENDURANTS physicalEndurant => PHYSICAL_ENDURANTS physicalEndurant where instance PHYSICAL_ENDURANTS WeatherStation where instance PHYSICAL_ENDURANTS AmountOfAir where class PHYSICAL_ENDURANTS amountOfMatter => AMOUNTS_OF_MATTER amountOfMatter where instance AMOUNTS_OF_MATTER WeatherStation where class PHYSICAL_ENDURANTS physicalObject => PHYSICAL_OBJECTS physicalObject where instance PHYSICAL_OBJECTS WeatherStation where class PHYSICAL_OBJECTS apo => APOS apo where getPosition :: apo -> Position instance APOS WeatherStation where getPosition (WeatherStation iD pos) = pos + 10
-- a data type declaration and data type constructor. data PHYSICAL_ENDURANTS physicalEndurant => Temperature physicalEndurant = Temperature physicalEndurant deriving Show -- Qualities the class of all quality types (= properties) is a constructor class -- its constructors can be applied to endurants, perdurants, qualities or abstracts class QUALITIES quality entity instance QUALITIES Temperature AmountOfAir class (APOS agent, QUALITIES quality entity) => OBSERVERS agent quality entity where observe :: quality entity -> agent -> IO Observation express :: quality entity -> agent -> Value observe quale agent = do clockTime <- getClockTime return (Observation (express quale agent) (getPosition agent) clockTime) instance OBSERVERS WeatherStation Temperature AmountOfAir where express (Temperature (AmountOfAir heat moisture)) weatherStation = Measure heat {- -- running the following express (Temperature (AmountOfAir 40 20)) (WeatherStation "rr" 6) -- Gives Measure 40.0 Measure 40.0 -- We can get the type: Value :t express (Temperature (AmountOfAir 40 20)) (WeatherStation "rr" 6) -}
Tá an teachtaireacht seo scanta ó thaobh ábhar agus víreas ag Seirbhís Scanta Ríomhphost de chuid Seirbhísí Faisnéise, ITBÁC agus meastar í a bheith slán. [1]http://www.dit.ie This message has been scanned for content and viruses by the DIT Information Services E-Mail Scanning Service, and is believed to be clean. [2]http://www.dit.ie
References
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (2)
-
Patrick Browne
-
Roman Cheplyaka