A "truly" generic function in Haskell - haskell

Suppose I have a compound data type -
data M o = M (String,o)
Now, I can define a function that works for ALL M irrespective of o. For example -
f :: M o -> M o
f (M (s,o)) = M (s++"!", o)
However, f is not really as general as I'd like it to be. In particular, using f in an expression fixes the type of o so I cannot use f again with a different type of o. For example the following does not typecheck -
p f = undefined where
m1 = M ("1", ())
m2 = M ("2", True)
m1' = f m1
m2' = f m2
It produces the error - Couldn't match expected type 'Bool' with actual type '()'
Surprisingly, if I don't provide f as an argument and instead simply use the global definition of f then it compiles and works fine! i.e. this compiles -
p = undefined where
m1 = M ("1", ())
m2 = M ("2", True)
m1' = f m1
m2' = f m2
Is there a particular reason for this? How can I work around this problem i.e. define a function f that can be applied to all (M o), even when the o varies within the same expression? I'm guessing existential types come into play here but I just can't figure out how.

The problem is that the compiler cannot infer the type of p properly. You'll have to give it a type signature:
p :: (forall o. M o -> M o) -> a
This is a rank 2 type, so you'll need a language extension:
{-# LANGUAGE Rank2Types #-}
or
{-# LANGUAGE RankNTypes #-}
Read more about it here: http://www.haskell.org/haskellwiki/Rank-N_types

Is there a particular reason for this?
Indeed, there is one. To say it in one sentence: type inference will not work properly if one lifts the restriction of the HM system that lambda arguments must be monomorphic.
Simon Peyton Jones has devised a type checker that extends HM and allows higher rank polymorphism. But in such cases, explicit type annotations are required. See Sjoerds Answer.

The f in the scope of the function p f is not the same as the top level function f. It is whatever function is given as the argument when p is called. Since you didn't give p a type signature, the compiler has to infer what f is from how you use it. Your first use implies that f :: M () -> M (), which means p :: (M () -> M ()) -> a. As someone else said, you have to give p an explicit signature using forall to do what you're trying to do.

Related

Simpler syntax for overloading function names

In Haskell with the type families extension, this is perfectly legal (ideone):
{-# LANGUAGE TypeFamilies #-}
type family F a
data A = A Int
data B = B Double
type instance F A = Int
type instance F B = Double
class Get a where
get :: a -> F a
instance Get A where
get (A x) = x
instance Get B where
get (B x) = x
main = print $ (get (A 3), get (B 2.0))
Basically I've defined two functions get.
One with type signature:
get :: A -> Int
And the second:
get :: B -> Double
However, there's a lot of cruft in the code above. What I'd like to be able to do is this:
get :: A -> Int
get (A x) = x
get :: B -> Double
get (B x) = x
I understand using this syntax exactly won't work, but is there any way I can get what I want to achieve without a dozen lines defining type instances and class instances? Considering first code works fine, I see no reason why the Haskell compiler can't this shorter code into the above anyway.
This should do the job:
class Get a b | a -> b where
get :: a -> b
instance Get A Int where
...
https://www.haskell.org/haskellwiki/Functional_dependencies
Okay, so it only got rid of type families. I don't think you can get rid of type classes, as they are the method of implementing overloading. Besides, without a class, you would not be able to express class constraints in types, e.g. you could not write this:
getPaired :: (Get a b, Get c d) => (a, c) -> (b, d)
I don't know if this is applicable to your use case - your example is rather contrived. But you can use a GADT instead of type classes here:
data T a where
A :: Int -> T Int
B :: Double -> T Double
get :: T a -> a
get (A x) = x
get (B x) = x
In general, there is no way to get the compiler to guess what code you want to write and write it for you. Such a compiler would obsolete a majority of programmers, I suspect, so we should all be glad it doesn't exist. I do agree that you are writing quite a lot to do very little, but perhaps that is a sign there is something wrong with your code, rather than a deficit in the compiler.
Here is another alternative:
{-# LANGUAGE TypeFamilies #-}
data A = A Int
data B = B Double
class Get a where
type F a
get :: a -> F a
instance Get A where
type F A = Int
get (A x) = x
instance Get B where
type F B = Double
get (B x) = x
main = print (get (A 3), get (B 2.0))
It looks nicer to me, than functional dependencies.
All the stuff is described at https://www.haskell.org/haskellwiki/GHC/Type_families

How can a function be "transparently augmented" in Haskell?

Situation
I have function f, which I want to augment with function g, resulting in function named h.
Definitions
By "augment", in the general case, I mean: transform either input (one or more arguments) or output (return value) of function f.
By "augment", in the specific case, (specific to my current situation) I mean: transform only the output (return value) of function f while leaving all the arguments intact.
By "transparent", in the context of "augmentation", (both the general case and the specific case) I mean: To couple g's implementation as loosely to f's implementation as possible.
Specific case
In my current situation, this is what I need to do:
h a b c = g $ f a b c
I am interested in rewriting it to something like this:
h = g . f -- Doesn't type-check.
Because from the perspective of h and g, it doesn't matter what arguments f take, they only care about the return value, hence it would be tight coupling to mention the arguments in any way. For instance, if f's argument count changes in the future, h will also need to be changed.
So far
I asked lambdabot on the #haskell IRC channel: #pl h a b c = g $ f a b c to which I got the response:
h = ((g .) .) . f
Which is still not good enough since the number of (.)'s is dependent on the number of f's arguments.
General case
I haven't done much research in this direction, but erisco on #haskell pointed me towards http://matt.immute.net/content/pointless-fun which hints to me that a solution for the general case could be possible.
So far
Using the functions defined by Luke Palmer in the above article this seems to be an equivalent of what we have discussed so far:
h = f $. id ~> id ~> id ~> g
However, it seems that this method sadly also suffers from being dependent on the number of arguments of f if we want to transform the return value of f -- just as the previous methods.
Working example
In JavaScript, for instance, it is possible to achieve transparent augmentation like this:
function h () { return g(f.apply(this, arguments)) }
Question
How can a function be "transparently augmented" in Haskell?
I am mainly interested in the specific case, but it would be also nice to know how to handle the general case.
You can sort-of do it, but since there is no way to specify a behavior for everything that isn't a function, you'll need a lot of trivial instances for all the other types you care about.
{-# LANGUAGE TypeFamilies, DefaultSignatures #-}
class Augment a where
type Result a
type Result a = a
type Augmented a r
type Augmented a r = r
augment :: (Result a -> r) -> a -> Augmented a r
default augment :: (a -> r) -> a -> r
augment g x = g x
instance Augment b => Augment (a -> b) where
type Result (a -> b) = Result b
type Augmented (a -> b) r = a -> Augmented b r
augment g f x = augment g (f x)
instance Augment Bool
instance Augment Char
instance Augment Integer
instance Augment [a]
-- and so on for every result type of every function you want to augment...
Example:
> let g n x ys = replicate n x ++ ys
> g 2 'a' "bc"
"aabc"
> let g' = augment length g
> g' 2 'a' "bc"
4
> :t g
g :: Int -> a -> [a] -> [a]
> :t g'
g' :: Int -> a -> [a] -> Int
Well, technically, with just enough IncoherentInstances you can do pretty much anything:
{-# LANGUAGE MultiParamTypeClasses, TypeFamilies,
FlexibleInstances, UndecidableInstances, IncoherentInstances #-}
class Augment a b f h where
augment :: (a -> b) -> f -> h
instance (a ~ c, h ~ b) => Augment a b c h where
augment = ($)
instance (Augment a b d h', h ~ (c -> h')) => Augment a b (c -> d) h where
augment g f = augment g . f
-- Usage
t1 = augment not not
r1 = t1 True
t2 = augment (+1) (+)
r2 = t2 2 3
t3 = augment (+1) foldr
r3 = t3 (+) 0 [2,3]
The problem is that the real return value of something like a -> b -> c isn't
c, but b -> c. What you want require some kind of test that tells you if a type isn't
a function type. You could enumerate the types you are interested in, but that's not so
nice. I think HList solve this problem somehow, look at the paper. I managed to understand a bit of the solution with overlapping instances, but the rest goes a bit over my head I'm afraid.
JavaScript works, because its arguments are a sequence, or a list, so there is just one argument, really. In that sense it is the same as a curried version of the functions with a tuple representing the collection of arguments.
In a strongly typed language you need a lot more information to do that "transparently" for a function type - for example, dependent types can express this idea, but require the functions to be of specific types, not a arbitrary function type.
I think I saw a workaround in Haskell that can do this, too, but, again, that works only for specific types, which capture the arity of the function, not any function.

Using fsharp-typeclasses to make a function that works on arbitrary monads

I'm trying to implement composM from the paper A pattern for almost compositional functions which accepts an arbitray monad and works on it. In Haskell the code would be:
data Expr =
| Var String
| Abs String Expr
composExprM :: (Monad m) => (Expr -> m Expr) -> Expr -> m Expr
composExprM f e =
case e of
Abs n e -> f e >>= (\e' -> return $ Abs n e')
_ -> return e
I tried using fsharp-typeclasses with the code below:
type Expr =
| Var of string
| Abs of string * Expr
let rec composExprM f e = match e with
| Abs (n, e) -> f e >>= (fun e' -> return' <| Abs (n, e'))
| Var _ -> return' e
But I get type inference errors:
> Could not resolve the ambiguity inherent in the use of the operator 'instance' at or near this program point. Consider using type annotations to resolve the ambiguity.
> Type constraint mismatch when applying the default type 'obj' for a type inference variable. No overloads match for method 'instance'. The available overloads are shown below (or in the Error List window). Consider adding further type constraints
> Possible overload: 'static member Return.instance : _Monad:Return * Maybe<'a> -> ('a -> Maybe<'a>)'. Type constraint mismatch. The type
obj
is not compatible with type
Maybe<'a>
The type 'obj' is not compatible with the type 'Maybe<'a>'.
> etc.....
Is what I'm trying to achieve possible with fsharp-typeclasses? Or do I have to restrict the function to only use a specific monad?
Keep in mind that polymorphic functions using this technique should be inline, that's where the "magic" resides.
So, just add the inline keyword after let rec and it will compile.
Please let me know if the function behaves as expected. I will have a look at that paper later.
In the samples you will find many functions defined to work with any Monad.
That was the main motivation when I started this project.

Type signature in a where clause

I've written a function similar to Data.Enumerator.List.map that makes an Iteratee compatible with an Enumerator that feeds a different Stream type.
import Data.Enumerator
test :: Monad m => (ao -> ai) -> Iteratee ai m b -> Iteratee ao m b
test f iter = go $$ iter
where go (Continue k) = continue $
\stream -> go $$ k (fmap f stream)
go (Yield res _) = yield res EOF
If I omit the type signature for go, this will work just fine.
However, I'd like to include it but I'm unable to determine what the correct signature should be.
Here's what I think it should be:
go :: Monad m => Step ai m b -> Iteratee ao m b
but that doesn't work.
I need some advice on finding the correct type signature for go.
You probably can't give go a type signature as-is.
The reason for this is that it makes use of polymorphic arguments bound by test. This means that, inside go, the identifier f has type (ao -> ai) for some specific, but unknown types ao and ai.
Type variables are generally only in scope for the single type signature where they're introduced, so when you give go its own type signature, the ao and ai there are new, polymorphic types, which of course causes a type error when trying to combine them with the similarly named, but fixed (and unknowable) types from test's signature.
The end result is that you can't write the type of go explicitly, which is not very satisfying. To solve this, GHC offers the ScopedTypeVariables extension, which allows bringing variables introduced in a type signature in scope inside the where clause of the function, among other things.
Note that if you only use the where clause to create an internal scope for definitions, and don't make use of identifiers bound by arguments to the outer function, you can write type signatures in the where clause just like you can for top level bindings. If you don't want to use GHC extensions, you can simply pass the parameters in redundantly. Something like this should work in that case:
test :: Monad m => (ao -> ai) -> Iteratee ai m b -> Iteratee ao m b
test f iter = go f $$ iter
where go :: Monad m => (ao -> ai) -> Step ai m b -> Iteratee ao m b
go f (Continue k) = continue $
\stream -> go f $$ k (fmap f stream)
go _ (Yield res _) = yield res EOF
You probably want that type, but with the ScopedTypeVariables extension enabled and with the variables from test's type signature in scope:
{-# LANGUAGE ScopedTypeVariables #-}
import Data.Enumerator
test :: forall m ai ao b. Monad m => (ao -> ai) -> Iteratee ai m b -> Iteratee ao m b
test f iter = go $$ iter
where go :: Step ai m b -> Iteratee ao m b
go (Continue k) = continue $
\stream -> go $$ k (fmap f stream)
go (Yield res _) = yield res EOF
See the GHC documentation for more information.

What does "exists" mean in Haskell type system?

I'm struggling to understand the exists keyword in relation to Haskell type system. As far as I know, there is no such keyword in Haskell by default, but:
There are extensions which add them, in declarations like these data Accum a = exists s. MkAccum s (a -> s -> s) (s -> a)
I've seen a paper about them, and (if I recall correctly) it stated that exists keyword is unnecessary for type system since it can be generalized by forall
But I can't even understand what exists means.
When I say, forall a . a -> Int, it means (in my understanding, the incorrect one, I guess) "for every (type) a, there is a function of a type a -> Int":
myF1 :: forall a . a -> Int
myF1 _ = 123
-- okay, that function (`a -> Int`) does exist for any `a`
-- because we have just defined it
When I say exists a . a -> Int, what can it even mean? "There is at least one type a for which there is a function of a type a -> Int"? Why one would write a statement like that? What the purpose? Semantics? Compiler behavior?
myF2 :: exists a . a -> Int
myF2 _ = 123
-- okay, there is at least one type `a` for which there is such function
-- because, in fact, we have just defined it for any type
-- and there is at least one type...
-- so these two lines are equivalent to the two lines above
Please note it's not intended to be a real code which can compile, just an example of what I'm imagining then I hear about these quantifiers.
P.S. I'm not exactly a total newbie in Haskell (maybe like a second grader), but my Math foundations of these things are lacking.
A use of existential types that I've run into is with my code for mediating a game of Clue.
My mediation code sort of acts like a dealer. It doesn't care what the types of the players are - all it cares about is that all the players implement the hooks given in the Player typeclass.
class Player p m where
-- deal them in to a particular game
dealIn :: TotalPlayers -> PlayerPosition -> [Card] -> StateT p m ()
-- let them know what another player does
notify :: Event -> StateT p m ()
-- ask them to make a suggestion
suggest :: StateT p m (Maybe Scenario)
-- ask them to make an accusation
accuse :: StateT p m (Maybe Scenario)
-- ask them to reveal a card to invalidate a suggestion
reveal :: (PlayerPosition, Scenario) -> StateT p m Card
Now, the dealer could keep a list of players of type Player p m => [p], but that would constrict
all the players to be of the same type.
That's overly constrictive. What if I want to have different kinds of players, each implemented
differently, and run them against each other?
So I use ExistentialTypes to create a wrapper for players:
-- wrapper for storing a player within a given monad
data WpPlayer m = forall p. Player p m => WpPlayer p
Now I can easily keep a heterogenous list of players. The dealer can still easily interact with the
players using the interface specified by the Player typeclass.
Consider the type of the constructor WpPlayer.
WpPlayer :: forall p. Player p m => p -> WpPlayer m
Other than the forall at the front, this is pretty standard haskell. For all types
p that satisfy the contract Player p m, the constructor WpPlayer maps a value of type p
to a value of type WpPlayer m.
The interesting bit comes with a deconstructor:
unWpPlayer (WpPlayer p) = p
What's the type of unWpPlayer? Does this work?
unWpPlayer :: forall p. Player p m => WpPlayer m -> p
No, not really. A bunch of different types p could satisfy the Player p m contract
with a particular type m. And we gave the WpPlayer constructor a particular
type p, so it should return that same type. So we can't use forall.
All we can really say is that there exists some type p, which satisfies the Player p m contract
with the type m.
unWpPlayer :: exists p. Player p m => WpPlayer m -> p
When I say, forall a . a -> Int, it
means (in my understanding, the
incorrect one, I guess) "for every
(type) a, there is a function of a
type a -> Int":
Close, but not quite. It means "for every type a, this function can be considered to have type a -> Int". So a can be specialized to any type of the caller's choosing.
In the "exists" case, we have: "there is some (specific, but unknown) type a such that this function has the type a -> Int". So a must be a specific type, but the caller doesn't know what.
Note that this means that this particular type (exists a. a -> Int) isn't all that interesting - there's no useful way to call that function except to pass a "bottom" value such as undefined or let x = x in x. A more useful signature might be exists a. Foo a => Int -> a. It says that the function returns a specific type a, but you don't get to know what type. But you do know that it is an instance of Foo - so you can do something useful with it despite not knowing its "true" type.
It means precisely "there exists a type a for which I can provide values of the following types in my constructor." Note that this is different from saying "the value of a is Int in my constructor"; in the latter case, I know what the type is, and I could use my own function that takes Ints as arguments to do something else to the values in the data type.
Thus, from the pragmatic perspective, existential types allow you to hide the underlying type in a data structure, forcing the programmer to only use the operations you have defined on it. It represents encapsulation.
It is for this reason that the following type isn't very useful:
data Useless = exists s. Useless s
Because there is nothing I can do to the value (not quite true; I could seq it); I know nothing about its type.
UHC implements the exists keyword. Here's an example from its documentation
x2 :: exists a . (a, a -> Int)
x2 = (3 :: Int, id)
xapp :: (exists b . (b,b -> a)) -> a
xapp (v,f) = f v
x2app = xapp x2
And another:
mkx :: Bool -> exists a . (a, a -> Int)
mkx b = if b then x2 else ('a',ord)
y1 = mkx True -- y1 :: (C_3_225_0_0,C_3_225_0_0 -> Int)
y2 = mkx False -- y2 :: (C_3_245_0_0,C_3_245_0_0 -> Int)
mixy = let (v1,f1) = y1
(v2,f2) = y2
in f1 v2
"mixy causes a type error. However, we can use y1 and y2 perfectly well:"
main :: IO ()
main = do putStrLn (show (xapp y1))
putStrLn (show (xapp y2))
ezyang also blogged well about this: http://blog.ezyang.com/2010/10/existential-type-curry/

Resources