Logically, it\'s possible to define universal transformation function, that can transform from any type to any type.
The possible way is:
{-#LANGUAG
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.
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