I have enclosed below a test file that causes an error that puzzles
me.  Both GHC and Hugs kick it out, so at least they agree; however, I
must admit that I don't understand it.

GHC gives the following error:

test.hs:1: Ambiguous context `{Physical taZ0}'
               `Physical taZ0' arising from use of `pulse' at test.hs:50
    When checking signature(s) for: `example2'

Hugs, on the other hand, gives:

ERROR "test.hs" (line 48): Ambiguous type signature in inferred type
*** ambiguous type : (Physical a, Physical b) => BasicSignal Time Voltage
*** assigned to    : example2

Again, this puzzles me.  When I start query types, I get:

:t pulse
pulse :: (Physical b, Physical a) => BasicSignal a b

There is something about field names here that causes this ambiguity;
as might be expected, 

:t Pulse
Pulse :: (Physical b, Physical a) => a -> a -> b -> BasicSignal a b
:t example1        
example1 :: BasicSignal Time Voltage

neither of which is a great surprise.  A hint is found by the
following two type queries (I have added two carrige returns for
clarity):

:t pulse{start_time=(Sec 1.0),pulse_width=(Sec 3.0),amplitude=(V 2.0)}
pulse{start_time = Sec 1.0, pulse_width = Sec 3.0, amplitude = V 2.0} :: 
  (Physical a, Physical b) => BasicSignal Time Voltage
Test> :t Pulse{start_time=(Sec 1.0),pulse_width=(Sec 3.0),amplitude=(V 2.0)}
Pulse{start_time = Sec 1.0, pulse_width = Sec 3.0, amplitude = V 2.0} :: 
  BasicSignal Time Voltage

Can anyone help here?  Why is the context carried over for pulse?  Are
partially resolved records usable in the presence of polymorphic
types?

Thanks for any and all help.

                                        Dave Barton <*>
                                        [EMAIL PROTECTED] )0(
                                        http://www.intermetrics.com/~dlb
----------------------------------------------------------------
module Test where

class Physical a where
  toPhysical:: Float -> a
  fromPhysical:: a -> Float

class Signal s where
  toSig:: (Physical a, Physical b) => (s a b) -> a -> b

data Time = Sec Float
data Voltage = V Float

instance Physical Time where
  toPhysical x = Sec x
  fromPhysical (Sec x) = x

instance Physical Voltage where
  toPhysical x = V x
  fromPhysical (V x) = x

data (Physical indep, Physical dep) => BasicSignal indep dep = 
    Pulse {start_time::indep,
           pulse_width::indep,
           amplitude::dep}

instance Signal BasicSignal where
  toSig Pulse{start_time,pulse_width,amplitude} = 
    let
      st = fromPhysical start_time
      pw = fromPhysical pulse_width
      zero = toPhysical 0.0
      chk t = 
        let ft = fromPhysical t
        in if ft < st then zero
           else if ft < (st + pw) then amplitude
           else zero
    in chk

pulse:: (Physical a, Physical b) => BasicSignal a b
pulse = Pulse{start_time = toPhysical 0.0}

example1:: BasicSignal Time Voltage
example1 = Pulse {start_time = (Sec 1.0),
                  pulse_width = (Sec 3.0),
                  amplitude = (V 2.0) }

example2:: BasicSignal Time Voltage
example2 = pulse {start_time = (Sec 1.0),
                  pulse_width = (Sec 3.0),
                  amplitude = (V 2.0) }



Reply via email to