Creating many similar newtypes/typeclass instances in Haskell
I am a beginner in Haskell and trying to learn about typeclasses and types. I have the following example (which represents a real problem in algebra that I am working on), in which I define a type which just wraps Num instances, and a typeclass which defines a binary operation baz
.
newtype Foo i = B i deriving (Eq, Ord, Show)
class Bar k where
baz :: k -> k -> k
instance Num k => Bar (Foo k) where
baz (B a) (B b) = B (f a b)
f :: Num a => a -> a -> a
f a b = a + b
When defining Bar
to be an instance of this, I realize that I want to be able to "vary" the function f
with the type. To be clear: I want to supply a function f :: Num a => a -> a -> a
and get back a new type Foo
which is an instance of Bar
. Say that I want to do this 5, 10 times with the only difference being different functions f
. I can of course copy and paste the code above, but I wonder if there is another way?
It seems to me that I'm confusing things. What is the best way of doing something like this in Haskell? Is this a good choice of design, what am I thinking right/wrong and why?
EDIT: I realize that a concrete example might help to make the question clearer (beware that it may seem complicated, I was not able to simplify the code more than this. The question above contains the same information I think): the typeclass I am interested in is Algebra kv
from the library HaskellForMaths:
class Algebra k b where
unit :: k -> Vect k b
mult :: Vect k (Tensor b b) -> Vect k b
Here k
is a field (a mathematical structure such as the real or complex numbers), while v
is a choice of basis in a vector space. I would want to use it something like this
newtype Basis i = T i deriving (Eq, Ord, Show)
type Expression k = Vect k (Basis Int)
instance Algebra k Basis where
unit x = x *> return I
mult = linear mult'
where mult' (T x ,T y) = comm x y
where comm a b = sum $ map (c -> structure a b c *> t c) [0..n]
t :: Int -> Expression k
t a = return (T a)
and then vary the map structure
as I please. Here the type T
is just a convenient way of writing abstract basis elements T 1, T 2, ...
. The reason I want to do it is the standard mathematical definition of an algebra in terms of its structure constants (here: structure
). To summarize: I want to be able to vary the function f
(preferably not at compile time?) and get back an algebra. This may be a bad design decision: if so, why?
You can use reflection. This is a fairly advanced technique, and there may be better ways to solve your problem, but the way you have stated it it seems like this is what you're looking for.
{-# LANGUAGE FlexibleContexts, RankNTypes, ScopedTypeVariables, UndecidableInstances #-}
import Data.Reflection
import Data.Proxy
class Bar k where
baz :: k -> k -> k
newtype Foo f i = B i -- f is a type level representation of your function
deriving (Eq, Ord, Show)
instance (Num k, Reifies f (k -> k -> k)) => Bar (Foo f k) where
baz (B a) (B b) = B (reflect (Proxy :: Proxy f) a b)
mkFoo :: forall i r. (i -> i -> i) -> i
-> (forall f. Reifies f (i -> i -> i) => Foo f i -> r) -> r
mkFoo f x c = reify f ((p :: Proxy f) -> c (B x :: Foo f i))
main = do
mkFoo (+) 5 $ foo1 -> do
print $ foo1 `baz` B 5 -- 10
mkFoo (*) 5 $ foo2 -> do
print $ foo2 `baz` B 5 -- 25
print $ foo1 `baz` foo2 -- type error
There is a lot going on here, so a few notes.
Reifies f (k -> k -> k)
is a constraint that means that f
is a type-level representation of a function of type k -> k -> k
. When we reflect (Proxy :: Proxy f)
(a fancy way of passing the type f
to reflect
since explicit type application was not until recently allowed), we get the function itself back out.
Now to the nasty signature of mkFoo
mkFoo :: forall i r. (i -> i -> i) -> i
-> (forall f. Reifies f (i -> i -> i) => Foo f i -> r) -> r
The first forall
is there for ScopedTypeVariables
, so we can refer to the type variables within the body of the function. The second one is a genuine rank-2 type,
(forall f. Reifies f (i -> i -> i) => Foo f i -> r) -> r
and it is a common encoding of an existential type, since Haskell doesn't have first class existentials. You can read this type as
exists f. ( Reifies f (i -> i -> i) , Foo f i )
or some such—it returns a type f
together with evidence that f
is a type-level representation of a function i -> i -> i
, and a Foo fi
. Observe in main
that to use this "existential", we call the function with continuation passing style, that is
mkFoo (+) 5 $ foo -> -- what to do with foo
Within the function, foo
behaves like it has type Foo f0 Integer
where f0
is a brand new type made just for this function.
It's quite nice that it won't let us baz
together Foo
s from different f
s, but unfortunately it's not smart enough to allow us to baz
together Foo
s made with the same function using different calls to mkFoo
, so:
mkFoo (+) 5 $ foo1 -> mkFoo (+) 5 $ foo2 -> foo1 `baz` foo2 -- type error
This is a supplement to my other answer, the solution I would actually suggest if your intention is to solve the practical problem rather than explore what is possible. It just converts the typeclass to "dictionary passing style", and doesn't use any fancy extensions or anything.
data Bar k = Bar { baz :: k -> k -> k }
newtype Foo i = B i
fooBar :: (i -> i -> i) -> Bar (Foo i)
fooBar f = Bar { baz = (B x) (B y) -> B (f x y) }
Then when you have a function that uses this, pass it a Bar
dictionary:
doThingsWithFoos :: Bar (Foo Int) -> Foo Int -> Foo Int -> Foo Int
doThingsWithFoos bar a b = baz bar a (baz bar a b)
It's a bit more verbose to use, but this kind of solution is remarkably flexible. Dictionaries are completely first-class, so, for example, you can start doing higher level manipulations on the dictionaries themselves:
transportBar :: (a -> b) -> (b -> a) -> Bar a -> Bar b
transportBar f finv bar = Bar { baz = x y -> f (baz bar (finv x) (finv y)) }
sumBar :: (Num a) => Bar a -> Bar a -> Bar a
sumBar bar1 bar2 = Bar { baz = x y -> baz bar1 x y + baz bar2 x y }
Both of these transformations would be a major pain using typeclasses.
This is actually not that different to the answer by luqui, but instead of defining the mapping from an phantom type f
to a concrete function at runtime using reify
we do this at compile time. This makes the code a bit simpler and easier to use.
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
class Bar k where
baz :: k -> k -> k
-- Foo has now another phantom type variable, that we use to pick the
-- desired f.
newtype Foo f k = B k
-- | GetF is used to retrieve a function for a given type label.
class GetF f k where
appF :: Foo f k -> Foo f k -> Foo f k
-- Now we can make an instance for Bar if we have an instance for GetF
instance GetF f k => Bar (Foo f k) where
baz x y = appF x y
-- = Usage example
-- | Add is just a label. We never use it at value level.
data Add
instance Num k => GetF Add k where
appF (B x) (B y) = B (x + y)
example :: Foo Add Int
example = B 1 `baz` B 2 -- = B 3
链接地址: http://www.djcxy.com/p/43464.html
上一篇: 我应该使用typeclasses或不?