simulating dynamic dispatch

Markus.Schnell@infineon.com Markus.Schnell@infineon.com
Fri, 21 Mar 2003 09:16:08 +0100


This message is in MIME format. Since your mail reader does not understand
this format, some or all of this message may not be legible.

------_=_NextPart_000_01C2EF82.201B9260
Content-Type: text/plain;
	charset="iso-8859-1"

I think you are looking like something done in the
HTML-Combinator-libraries.
I tried something like that some time ago, but didn't finish. But perhaps
you
can get an idea from that. See the files with this mail. (The code is in
unknown condition.)

Markus

> ah, yes.  i was aware that would work.  i forgot to mention 
> the constraint
> that i don't want the user to have to use the MkFoo/MkBar
> constructors.  if i could use them internally to 'test', that would be
> great, but that's what i couldn't get to work :).


------_=_NextPart_000_01C2EF82.201B9260
Content-Type: application/octet-stream;
	name="SaveExFStruct.hs"
Content-Transfer-Encoding: quoted-printable
Content-Disposition: attachment;
	filename="SaveExFStruct.hs"

{- (C)2002 Markus Schnell -}=0A=
=0A=
module Main=0A=
where=0A=
=0A=
{-=0A=
    This module demonstrates the use of the FStruct module.=0A=
-}=0A=
=0A=
import SaveFStruct=0A=
=0A=
main =3D do=0A=
  putStrLn "The FStruct module, Markus Schnell, 2002"=0A=
  putStrLn "----------------------------------------"=0A=
  =0A=
  let exf =3D [name =3D: [vorname =3D: "Peter", nachname =3D: "Post"], =
age =3D: (23::Int)]=0A=
  let fa  =3D [vorname =3D: "Peter"]=0A=
  let fb  =3D [nachname =3D: "Post"]=0A=
      af  =3D [vorname =3D: "Paul"]=0A=
  let fc  =3D fa ! fb =0A=
      fd  =3D fa ! fa=0A=
      fe  =3D fa ! af=0A=
  putStrLn (show exf)=0A=
  putStrLn (show fc)=0A=
  putStrLn (show fd)=0A=
  putStrLn (show fe)=0A=
  =0A=
--- Es darf nicht beliebige Strukturen geben, the Structures should be =
given Types=0A=
name     =3D mkArg "name"=0A=
vorname  =3D mkArg "vorname"=0A=
nachname =3D mkArg "nachname"=0A=
age      =3D mkArg "age"=0A=
=0A=
=0A=
=0A=
{- =3D=3D=3D=3D=3D=3D List of Examples =3D=3D=3D=3D=3D=3D -}=0A=
=0A=
-- Examples that should work --=0A=
-- indexing=0A=
=0A=
-- Examples that shouldn't work --=0A=
-- e.g. wrong types=0A=
=0A=

------_=_NextPart_000_01C2EF82.201B9260
Content-Type: application/octet-stream;
	name="SaveFStruct.hs"
Content-Transfer-Encoding: quoted-printable
Content-Disposition: attachment;
	filename="SaveFStruct.hs"

{- Author: Markus Schnell, 2002 -}=0A=
=0A=
-- This module may be used freely. Direct comments to =
haskell@markusschnell.com=0A=
=0A=
module SaveFStruct	-- Feature Structure=0A=
  (FStruct=0A=
  ,Argument=0A=
  ,mkArg	-- :: String -> Argument=0A=
  ,VALUE	=0A=
  ,Value(Val)=0A=
  ,(=3D:)		-- :: (VALUE a) =3D> Argument -> a -> Feature=0A=
  ,(!)		-- :: FStruct -> FStruct -> Maybe FStruct (unification)=0A=
  )=0A=
where=0A=
=0A=
{-=0A=
    What should the interface of a feature structure look like?=0A=
    Has anybody comments?=0A=
    How can I avoid (3::Int) for Integers?=0A=
-}=0A=
=0A=
{-=0A=
    A feature structure is a data type with a collection of attributes, =
which=0A=
    have values. These values can be atomic or can b e feature =
structures=0A=
    themselves.=0A=
    To have more control and safety one has to specify which values are =
possible=0A=
    for some feature. This can be done with a class system.=0A=
-}=0A=
=0A=
import List=0A=
import Monad=0A=
=0A=
=0A=
=0A=
=0A=
=0A=
{- =3D=3D=3D=3D=3D=3D Values =3D=3D=3D=3D=3D=3D -}=0A=
=0A=
{- Zun=8Achst muss ich das Problem l=9Asen, dass Int und String ohne =
explizite Angabe =0A=
   in den Typ Value umgewandelt werden -}=0A=
   =0A=
newtype Value =3D Val String deriving Eq=0A=
=0A=
class VALUE a where=0A=
  toValue         ::  a  -> Value=0A=
  toValueFromList :: [a] -> Value=0A=
  toValueFromList xs =3D Val ("[" ++ (concat . intersperse ", ") [x | =
(Val x) <- map toValue xs] ++ "]")=0A=
  =0A=
instance (VALUE a) =3D> VALUE [a] where=0A=
  toValue xs =3D toValueFromList xs=0A=
  =0A=
instance VALUE Value where=0A=
  toValue a =3D a=0A=
  =0A=
instance VALUE Int where=0A=
  toValue a =3D Val (showint a)=0A=
    where showint :: Int -> String=0A=
          showint =3D show=0A=
=0A=
instance VALUE Char where=0A=
  toValue a =3D Val (show a)=0A=
  toValueFromList str =3D Val (show str)=0A=
  =0A=
=0A=
instance Show Value where=0A=
  showsPrec _ (Val s) =3D showString s=0A=
=0A=
=0A=
=0A=
=0A=
=0A=
=0A=
{- =3D=3D=3D=3D=3D=3D Feature Structures =3D=3D=3D=3D=3D=3D -}=0A=
=0A=
type FStruct    =3D [Feature]=0A=
data Feature    =3D (:=3D) { arg :: Argument, val :: Value }=0A=
newtype Argument =3D Arg String deriving Eq=0A=
=0A=
(=3D:) :: (VALUE a) =3D> Argument -> a -> Feature=0A=
arg =3D: val =3D arg :=3D (toValue val)=0A=
=0A=
instance VALUE Feature where=0A=
  toValue f =3D Val (show f)=0A=
  =0A=
mkArg :: String -> Argument=0A=
mkArg =3D Arg . id=0A=
 =0A=
instance Show Feature where=0A=
  showsPrec _ (Arg arg :=3D Val s) =3D showString (arg ++ " =3D: " ++ =
s)=0A=
  =0A=
  =0A=
=0A=
=0A=
=0A=
=0A=
{- =3D=3D=3D=3D=3D=3D Unification =3D=3D=3D=3D=3D=3D -}=0A=
=0A=
{- Unification can fail -> Maybe -}=0A=
=0A=
(!) :: FStruct -> FStruct -> Maybe FStruct=0A=
(!)  =3D foldM (flip merge)=0A=
=0A=
-- put feature into structure=0A=
merge :: Feature -> FStruct -> Maybe FStruct=0A=
merge feat fs =3D=0A=
  if null sameArg=0A=
    then Just (feat:fs)=0A=
    else if val feat =3D=3D val (head sameArg)=0A=
           then Just fs=0A=
           else Nothing		-- unification failed=0A=
  where=0A=
    sameArg =3D filter (\x -> arg x =3D=3D arg feat) fs=0A=

------_=_NextPart_000_01C2EF82.201B9260--