matching types in Haskell

Hi, I wish to align or match some Haskell types in order to represent a set of ontologies and their embedded concpts [1]. I am not sure wheather modules or classes could be used. I have done this task in a language called Maude[2]. The code is below. I appreciate that Maude is not very popular so there is a brief description below. This diagram below represents the semantics of what I am trying to achive. I want to construct MERGEDONTOLOGY from ONTOLOGY1 and ONTOLOGY2 both of which are based on COMMON. MERGEDONTOLOGY { Woman, RiverBank, FinancialBank, HumanBeing} /\ /\ / \ / \ / \ / \ / \ / \ ONTOLOGY1 ONTOLOGY2 {Woman, Bank, Person} {Woman, Bank, Human} /\ /\ \ / \ / \ / \ / \ / \ / \ / {Woman , Person} COMMMON Each Maude module represents (below) a distinct ontology, each sort (or type in Haskell) represents a concept. This example includes both synonyms and homonyms. I want to align ONTOLOGY1 and ONTOLOGY2 w.r.t COMMON to produce MERGEDONTOLOGY. The details of the concepts are as follows. The Woman concept should be the same in all ontologies, there is only one Woman concept and it is named as such in each ontology. Hence there should be only one Woman.MERGEDONTOLOGY There is only one concept HumanBeing.MERGEDONTOLOGY, but there are 3 synonyms Human.ONTOLOGY2, Person.ONTOLOGY1, and Person.COMMON It would seem that Person.COMMON should be mapped (or renamed?) to Human.ONTOLOGY2 which in turn is renamed (or mapped) to HumanBeing.MERGEDONTOLOGY. The homonyms are Bank.ONTOLOGY1 and Bank.ONTOLOGY2 which should become distinct entities in RiverBank.MERGEDONTOLOGY and FinancialBank.MERGEDONTOLOGY My question is how should this be done in Haskell. Is there a classes only solution? Is ther a module only solution? Or do I need both? Regards, Pat ============================================= Brief description of Maude code In the Maude Language the module is the basic conceptual unit. Sorts are declared in modules Every line ends with a space dot. In this case each module is bracketed by fth .. endfth There are various types of mappings between modules. In this case I used renamings where the syntax is *( name_in_source_module to name_in_target_module....) The keyword protecting is a type of inport. The + symbol between the modules forms a new module that includes all the information in each of its arguments ============================== fth COMMON is sorts Woman Person . endfth fth ONTOLOGY1 is protecting COMMON . sorts Bank . endfth fth ONTOLOGY2 is protecting COMMON *( sort Person to Human) . sorts Bank . endfth fth MERGEDONTOLOGY is including (ONTOLOGY1 * (sort Bank to RiverBank,sort Person to HumanBeing)) + (ONTOLOGY2 * (sort Human to HumanBeing, sort Bank to FinancialBank)) . endfth with the command show all MERGEDONTOLOGY the system will produce the following module fth MERGEDONTOLOGY0 is sorts Woman HumanBeing FinancialBank RiverBank . endfth ================================ Reference [1]Shapes of Alignments Construction, Combination, and Computation by Oliver Kutz, Till Mossakowsk, and Mihai Codescu http://www.informatik.uni-bremen.de/~okutz/shapes.pdf [2] Informa tiom on Maude at: http://maude.cs.uiuc.edu/

Hi, Below are two attempts to define Peano arithmetic in Haskell. The first attempt, Peano1, consists of just a signature in the class with the axioms in the instance. In the second attempt, Peano2, I am trying to move the axioms into the class. The reason is, I want to put as much specification as possible into the class. Then I would like to include properties in the class such as commutativity something like: infixl 5 `com` com :: Int -> Int -> Int x `com` y = (x + y) commutative com a b = (a `com` b) == (b `com` a) I seem to be able to include just one default equation the Peano2 attempt. Any ideas? I have looked at http://www.haskell.org/haskellwiki/Peano_numbers Regards, Pat -- Attempt 1 -- In this attempt the axioms are in the instance and things seem OK module Peano1 where infixl 6 `eq` infixl 5 `plus` class Peano1 n where suc :: n -> n eq :: n -> n -> Bool plus :: n -> n -> n data Nat = One | Suc Nat deriving Show instance Peano1 Nat where suc = Suc One `eq` One = True (Suc m) `eq` (Suc n) = m `eq` n _`eq`_ = False m `plus` One = Suc m m `plus` (Suc n) = Suc (m `plus` n) -- Evaluation *Peano1> Suc(One) `plus` ( Suc (One)) -- Attempt 2 -- In this attempt the axioms are in the class and things are not OK. module Peano2 where infixl 6 `eq` infixl 5 `plus` class Peano2 n where one :: n eq :: n -> n -> Bool plus :: n -> n -> n suc :: n -> n suc a = a `plus` one {- I cannot add the remaining default axioms one `eq` one = True (suc m) `eq` (suc n) = m `eq` n (suc a) `eq` (suc b) = a `eq` b _`eq`_ = False -}

The problem is that you are using 'suc' as if it is a constructor: ((suc m)
`eq` (suc n) = m `eq` n)
You'll have to change it to something else, and it will probably require
adding an unpacking function to your class and it will probably be messy.
I'd suggest you make use of the Eq typeclass and defined the Eq instances
separately:
class (Eq n) => Peano2 n where
one :: n
plus :: n -> n -> n
suc :: n -> n
suc a = a `plus` one
- Job
On Thu, Sep 17, 2009 at 2:36 PM, pat browne
Hi, Below are two attempts to define Peano arithmetic in Haskell. The first attempt, Peano1, consists of just a signature in the class with the axioms in the instance. In the second attempt, Peano2, I am trying to move the axioms into the class. The reason is, I want to put as much specification as possible into the class. Then I would like to include properties in the class such as commutativity something like: infixl 5 `com` com :: Int -> Int -> Int x `com` y = (x + y) commutative com a b = (a `com` b) == (b `com` a)
I seem to be able to include just one default equation the Peano2 attempt. Any ideas? I have looked at http://www.haskell.org/haskellwiki/Peano_numbers
Regards, Pat
-- Attempt 1 -- In this attempt the axioms are in the instance and things seem OK module Peano1 where infixl 6 `eq` infixl 5 `plus`
class Peano1 n where suc :: n -> n eq :: n -> n -> Bool plus :: n -> n -> n
data Nat = One | Suc Nat deriving Show
instance Peano1 Nat where suc = Suc One `eq` One = True (Suc m) `eq` (Suc n) = m `eq` n _`eq`_ = False m `plus` One = Suc m m `plus` (Suc n) = Suc (m `plus` n) -- Evaluation *Peano1> Suc(One) `plus` ( Suc (One))
-- Attempt 2 -- In this attempt the axioms are in the class and things are not OK. module Peano2 where infixl 6 `eq` infixl 5 `plus`
class Peano2 n where one :: n eq :: n -> n -> Bool plus :: n -> n -> n suc :: n -> n suc a = a `plus` one
{- I cannot add the remaining default axioms one `eq` one = True (suc m) `eq` (suc n) = m `eq` n (suc a) `eq` (suc b) = a `eq` b _`eq`_ = False -}
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

I don't understand your goal. Isn't Peano arithmetic summarized in Haskell as: data Peano = Zero | Succ Peano deriving Eq This corresponds to a first-order logic over a signature that has equality, a constant symbol 0, and a one-place successor function symbol S. Function symbols such as < and + can be introduced as defined function symbols that do not add substantive information to the theory. The only axioms you want are the ones for equality. John
participants (3)
-
Job Vranish
-
John D. Ramsdell
-
pat browne