[Haskell-cafe] Re: subsequence

MR K P SCHUPKE k.schupke at imperial.ac.uk
Wed Oct 20 05:18:12 EDT 2004


Well I don't just want to give you the answer, but this code
finds a subsequence in a list... This is from the HList library,
and it looks for an ordered subtype ... but it also does what you
want (it uses a four valued modal logic, which returns AllFalse, if
list a is not a subtype (in-order) of b, (if the types are different
there is no point in comparing values) or it returns SomeTrue, which
has a value of either True or False depending on whether the list is
an ordered sublist of values.

--------------------------------------------------------------------

-- test for list a containing list b (elements of b occur in-order, but may
-- be interleaved with other elements.

class (HList r,HList s) => HContains' r s where
   hContains' :: r -> s -> Bool
instance HContains' HNil HNil where
   hContains' _ _ = True
instance HList r => HContains' (HCons a r) HNil where
   hContains' _ _ = True
instance HList r => HContains' HNil (HCons a r) where
   hContains' _ _ = False
instance (HContains' r (HCons a s),HContains' r s,Eq a) => HContains' (HCons a r) (HCons a s) where
   hContains' (HCons a r) s@(HCons a' s') = if a == a'
      then hContains' r s'
      else hContains' r s
instance HContains' r (HCons b s) => HContains' (HCons a r) (HCons b s) where
   hContains' (HCons _ r) s = hContains' r s

class (HList r,HList s,Logic.MBool t) => HContains'' r s t | r s -> t where
   hContains'' :: r -> s -> t
instance HContains'' HNil HNil Logic.AllTrue where
   hContains'' _ _ = Logic.AllTrue
instance HList r => HContains'' (HCons a r) HNil Logic.AllTrue where
   hContains'' _ _ = Logic.AllTrue
instance HList r => HContains'' HNil (HCons a r) Logic.AllFalse where
   hContains'' _ _ = Logic.AllFalse
instance HContains'' r s t => HContains'' (HCons a r) (HCons a s) t where
   hContains'' (_ :: HCons a r) (_ :: HCons b s) = hContains'' (undefined :: r) (undefined :: s)
instance HContains'' r s t => HContains'' (HCons a r) s t where
   hContains'' (_ :: HCons a r) s = hContains'' (undefined :: r) s

class (HContains' r s,Logic.Modal t) => HContains r s t | r s -> t where
   hContains :: r -> s -> t
instance HContains' r HNil => HContains r HNil Logic.AllTrue where
   hContains _ _ = Logic.AllTrue
instance (HContains'' r (HCons b s) t',Logic.And t' Logic.SomeTrue t,HContains' r (HCons b s)) => HContains r (HCons b s) t where
   hContains r s = hContains'' r s `Logic.and` Logic.toSomeTrue (hContains' r s)

----------------------------------------------------------------------------

Keean.


More information about the Haskell-Cafe mailing list