问题
Logically, it's possible to define universal transformation function, that can transform from any type to any type.
The possible way is:
{-#LANGUAGE MultiParamTypeClasses #-}
{-#LANGUAGE FlexibleInstances #-}
class FromTo a b where
fromTo:: a->b
instance FromTo a a where fromTo = id
instance FromTo Int Double where fromTo = fromIntegral
instance FromTo Int Float where fromTo = fromIntegral
instance FromTo Integer Double where fromTo = fromIntegral
instance FromTo Integer Float where fromTo = fromIntegral
instance FromTo Double Int where fromTo = round
instance FromTo Double Integer where fromTo = round
instance FromTo Float Int where fromTo = round
instance FromTo Float Integer where fromTo = round
-- e.t.c.
Well, it work's, it's extendable. But it's very bulky, because I must list any case I want to use.
Is there any good solutions for this?
The neat one solution could be done like this, if it was correct (but it's not):
{-#LANGUAGE MultiParamTypeClasses #-}
{-#LANGUAGE FlexibleInstances #-}
{-#LANGUAGE InstanceSigs #-}
class FromTo a b where
fromTo:: a->b
instance (Integral a, Num b) => FromTo a b where
fromTo::a->b
fromTo x = (fromIntegral x)
{---Commented, because addition breaks program.-------------------------------
instance (RealFrac a, Integral b) => FromTo a b where
fromTo::a->b
fromTo x = (round x)
-}
Maybe it would be possible if there was some type sets extension (Haskell-like pseudo code):
{-#LANGUAGE MultiParamTypeClasses #-}
{-#LANGUAGE FlexibleInstances #-}
{-#LANGUAGE InstanceSigs #-}
{-#LANGUAGE TypeSets #-}
class FromTo a b where
fromTo:: a->b
instance setfrom (Integral a, Num b). (Integral a, Num b) => FromTo a b where
fromTo::a->b
fromTo x = (fromIntegral x)
instance setfrom (RealFrac a, Integral b). (RealFrac a, Integral b) => FromTo a b where
fromTo::a->b
fromTo x = (round x)
setfrom C1 a.
here should define set of types, using instances information from C1
class. The compiler should check if instances are intersects. The other possible construction of this extension is set (T1,T2,...,TN) a.
, that allows to merely define the type set.
UPD 1
The 1-st solution could be improved this way (but it's incorrect way):
{-#LANGUAGE MultiParamTypeClasses #-}
{-#LANGUAGE FlexibleInstances #-}
class FromTo a b where
fromTo:: a->b
instance FromTo a a where fromTo = id
instance Num b => FromTo Int b where
fromTo x = fromIntegral x
instance Num b => FromTo Integer b where
fromTo x = fromIntegral x
instance Integral b => FromTo Float b where
fromTo x = round x
instance Integral b => FromTo Double b where
fromTo x = round x
But it's still not good and, in addition, gives overlaps when calling in interactive mode:
*Main> fromTo (10::Double) ::Double
<interactive>:108:1:
Overlapping instances for FromTo Double Double
arising from a use of `fromTo'
Matching instances:
instance FromTo a a -- Defined at 4.hs:8:10
instance Integral b => FromTo Double b -- Defined at 4.hs:19:10
In the expression: fromTo (10 :: Double) :: Double
In an equation for `it': it = fromTo (10 :: Double) :: Double
回答1:
From what I understand, you want to parameterize class instances by the constraints on the types. This is possible with modern GHC extensions:
{-#LANGUAGE MultiParamTypeClasses, FlexibleInstances, InstanceSigs, ConstraintKinds,
KindSignatures, DataKinds, TypeOperators, UndecidableInstances, GADTs #-}
import GHC.Prim(Constraint)
class ConstrainedBy (cons :: [* -> Constraint]) (t :: *) where
instance ConstrainedBy '[] t
instance (x t, ConstrainedBy xs t) => ConstrainedBy (x ': xs) t
The purpose of this class is to allow multiple constraints on a single type in the FromTo
class. For example, you could decide that Num a, Real a => Floating a
has a different instance than Num a => Floating a
(this is a contrived example - but depending on your use cases, you may have need for this functionality).
Now we 'lift' this class to the data level with a GADT:
data ConsBy cons t where
ConsBy :: ConstrainedBy cons t => t -> ConsBy cons t
instance Show t => Show (ConsBy cons t) where
show (ConsBy t) = "ConsBy " ++ show t
Then, the FromTo
class:
class FromTo (consa:: [* -> Constraint]) (a :: *) (consb :: [* -> Constraint]) (b :: *) where
fromTo :: ConsBy consa a -> ConsBy consb b
I don't believe that there is a way to have the type that you specified for the function fromTo
; if the type is simply a -> b
, there is no way to deduce the constraints from the function arguments.
And your instances:
instance (Integral a, Num b) => FromTo '[Integral] a '[Num] b where
fromTo (ConsBy x) = ConsBy (fromIntegral x)
instance (RealFrac a, Integral b) => FromTo '[RealFrac] a '[Integral] b where
fromTo (ConsBy x) = ConsBy (round x)
You have to state all the constraints twice, unfortunately. Then:
>let x = ConsBy 3 :: Integral a => ConsBy '[Integral] a
>x
ConsBy 3
>fromTo x :: ConsBy '[Num] Float
ConsBy 3.0
You can have instances that would normally be considered 'overlapping':
instance (Integral a, Eq b, Num b) => FromTo '[Integral] a '[Num, Eq] b where
fromTo (ConsBy x) = ConsBy (fromIntegral x + 1) -- obviously stupid
>let x = ConsBy 3 :: Integral a => ConsBy '[Integral] a
>fromTo x :: Num a => ConsBy '[Num] a
ConsBy 3
>fromTo x :: (Num a, Eq a) => ConsBy '[Num, Eq] a
ConsBy 4
On the other hand, if you wish to make the assertion that there is only one instance that can match a combination of type and constraints (making the above impossible), you can use functional dependencies to do this:
{-# LANGUAGE FunctionalDependencies #-}
class FromTo (consa:: [* -> Constraint]) (a :: *) (consb :: [* -> Constraint]) (b :: *)
| consa a -> consb b, consb b -> consa a
where
fromTo :: ConsBy consa a -> ConsBy consb b
Now the third instance that I wrote is invalid, however, you can use fromTo
without explicit type annotations:
>let x = ConsBy 3 :: Integral a => ConsBy '[Integral] a
>fromTo x
ConsBy 3
>:t fromTo x
fromTo x
:: Num b =>
ConsBy ((':) (* -> Constraint) Num ('[] (* -> Constraint))) b
As you can see, the output type, Num b => b
, is inferred from the input type. This works the same for polymorphic and concrete types:
>let x = ConsBy 3 :: ConsBy '[Integral] Int
>:t fromTo x
fromTo x
:: Num b =>
ConsBy ((':) (* -> Constraint) Num ('[] (* -> Constraint))) b
回答2:
One solution is to use Template Haskell. You'd still need to explicitly add all the types (instead of sets of types as typeclasses implies) but it would be shorter:
{-# LANGUAGE TemplateHaskell #-}
-- ...
let x = mkName "x"
list = [ (''Double, ''Int, 'floor)
, (''Float, ''Int, 'floor)
]
mkI tyA tyB op =
instanceD
(cxt [])
(appT (appT (conT ''FromTo) (conT tyA)) (conT tyB))
[ funD 'fromTo [clause [] (normalB iOp) []]
, pragInlD 'fromTo Inline FunLike AllPhases
]
in sequence [ mkI a b op | (a,b,op) <- list ]
With the above (untested) Template Haskell splice you can enumerate pairs of types and the operation for the conversion. This still requires you to type n choose 2
pairs into the list.
Alternatively, you could have a list of source types (tyA) and a separate list of target types (tyB) then convert between all the source types and all destination types - this strategy would be simple for similar types (all floats to all integrals) and save you some typing, but it isn't general enough for all conversions.
来源:https://stackoverflow.com/questions/20270883/universal-type-tranformer-in-haskell