> {-# LANGUAGE ScopedTypeVariables #-}
> module Main where {
Haskell's Data.Dynamic is rather nifty, allowing postponing type-checking until runtime.
> import Data.Dynamic;
> import Control.Monad(foldM);
> import Data.Maybe(fromJust);
This function takes a list of functions of different types [ a->b, b->c, c->d ] and composes them returning a->d, essentialy "fold (.)", a task unthinkable before Data.Dynamic.
Each function needs to be converted into Dynamic, and the result of the composition is wrapped in a Maybe if there is a type error. foldM uses the fact that Maybe is a Monad.
Type errors return "Nothing". It would be nice if there were a way to get more specific error messages.
> compose_list :: [Dynamic] -> Dynamic -> Maybe Dynamic;
> compose_list fs start = foldM (flip dynApply) start (reverse fs);
This function allows creating a list of functions for input into compose_list.
> cons :: Typeable a => a -> [Dynamic] -> [Dynamic];
> cons f fs = (toDyn f):fs;
Let us test it.
> my_list_of_funcs :: [Dynamic];
> my_list_of_funcs = cons h $ cons g $ cons dbl [];
> dbl :: String -> [String];
> dbl x = [x,x];
> g :: [String] -> [String];
> g x = "hello":x;
> h :: [String] -> [String];
> h = map (take 3);
Data.Dynamic cannot handle polymorphic functions. If the type signature were
h :: (Typeable a) => [[a]] -> [[a]];
then we get a pretty confusing error message:
Ambiguous type variable `a0' in the constraint: (Typeable a0) arising from a use of `h' Probable fix: add a type signature that fixes these type variable(s) In the first argument of `cons', namely `h' In the expression: cons h In the expression: cons h $ cons g $ cons dbl []
> main :: IO ();
> main = case compose_list my_list_of_funcs (toDyn "world") of {
> Nothing -> putStrLn "1 fail";
> Just (i1::Dynamic) -> case (fromDynamic i1) of {
> Nothing -> putStrLn "2 fail";
> Just (i2::[String]) -> print i2;
> };
> };
output:
["hel","wor","wor"]
> }
>
3 comments :
{-# LANGUAGE GADTs #-}
data Flist a b where
Nil :: Flist a a
Cons :: (a -> b) -> Flist b c -> Flist a c
compose :: Flist a b -> a -> b
compose Nil x = x
compose (Cons f fs) x = compose fs (f x)
h :: Typeable a => [a] -> [a]
is wrong. What GHC was trying to say was:
h :: [[a]] -> [[a]]
Thanks upok! I'm going to update the post. For historical reference, the post originally said:
If the type signature were
h :: (Typeable a) => [a] -> [a];
then we get a pretty confusing error message:
Could not deduce (a ~ [a0])
from the context (Typeable a)
bound by the type signature for h :: Typeable a => [a] -> [a]
at file.lhs:48:5-20
`a' is a rigid type variable bound by
the type signature for h :: Typeable a => [a] -> [a]
at file.lhs:48:5
Expected type: a -> a
Actual type: [a0] -> [a0]
In the return type of a call of `take'
In the first argument of `map', namely `(take 3)'
Post a Comment