
On Thu, Oct 02, 2003 at 06:42:59PM -0700, oleg@pobox.com wrote:
data Datatype ex = forall vt . Datatype (DatatypeVal ex vt)
In practice one rarely would write forall vt. Datatype (DatatypeVal ex vt) unless he is writing something like the ST monad. You can only pass vt to functions with the signature forall vt. vt -> C1 vt C2 C3 ...
where C1, C2, C3 do not depend on vt in any way. For example, functions like 'id', (\vt x -> (vt,x)), (\x -> 1), etc. As you can notice these functions don't do anything with their vt argument. They merely pass it through or disregard. You can't do anything with the unconstrainedly quantified argument!
I think I have used unconstrained existentially quantified types in a useful way. Below is a combinator library for calculating statistics with aggregate functions (type Stat). I use a datatype 'Stat i o' to represent an aggregate function that can be fed with values of type 'i' and returns a result of type 'o'. I use existentially quantified constructor to hide the internal state of particular aggregate function. For example, avg's internal state is a pair of numbers, but it is hidden, because users of the library shouldn't have to know that. However this approach has caveats. For example you can't store the state of Stat and restart it later. All steps are done within one call to runStat. Example uses: {- average of the list of values -} runStat avg [1..20] 10.5 {- separate average for odd and even numbers -} runStat (fmap fmToList (categorize even (projectInput fromIntegral avg))) [1..20] [(False,10.0),(True,11.0)] {- word frequency -} runStat rank (words "this is a test is a test") [(2,"test"),(2,"is"),(2,"a"),(1,"this")] {- group words by lengths -} runStat (fmap fmToList (categorize length (fold (flip (:)) []))) (words "a aa ba wwww zz") [(1,["a"]),(2,["zz","ba","aa"]),(4,["wwww"])] ... etc Best regards, Tom ---------------------------------------------------------------------- {-# OPTIONS -fglasgow-exts #-} module Stat where import Data.FiniteMap import Prelude hiding (sum) import List (sort) data Stat i o = -- aggregate function taking i's on input and producing o forall s. Stat s -- init (s -> i -> s) -- update (s -> o) -- result runStat :: Stat i o -> [i] -> o runStat (Stat init update result) l = result (foldl update init l) fold :: (a -> b -> a) -> a -> Stat b a fold f i = Stat i f id count :: Num n => Stat a n count = fold (\s _ -> s+1) 0 sum :: Num n => Stat n n sum = fold (+) 0 pair :: Stat a b -> Stat a c -> Stat a (b,c) pair (Stat init1 update1 result1) (Stat init2 update2 result2) = Stat (init1, init2) (\(s1,s2) x -> (update1 s1 x, update2 s2 x)) (\(s1,s2) -> (result1 s1, result2 s2)) instance Functor (Stat a) where fmap f (Stat init update result) = (Stat init update (f . result)) projectInput :: (i -> j) -> Stat j a -> Stat i a projectInput f (Stat init update result) = Stat init (\s i -> update s (f i)) result avg :: Fractional n => Stat n n avg = fmap (\(s,c) -> if c /= 0 then s/c else 0) (pair sum count) avgMaybe :: Fractional n => Stat n (Maybe n) avgMaybe = fmap (\(s,c) -> if c /= 0 then Just (s/c) else Nothing) (pair sum count) categorize :: Ord k => (a -> k) -> Stat a b -> Stat a (FiniteMap k b) categorize fk (Stat init update result) = Stat emptyFM (\fm a -> addToFM fm (fk a) (update (maybe init id (lookupFM fm (fk a))) a)) (mapFM (const result)) rank :: Ord k => Stat k [(Int,k)] rank = fmap (reverse . sort . (map(\(k,c)->(c,k))) . fmToList) (categorize id count) -- .signature: Too many levels of symbolic links