what are correct ways to translate haskell code ?

let's consider this example Alice has 1.hs like this v :: (,) Int Bool v = (,) 0 False main :: IO () main = putStrLn "print some magic number" >> print ( fst v ) Bob download 1.hs from Alice Bob would like to change 1.hs to 2.hs Bob want the programs [ 1.hs 2.hs ] to behave the same the reason that Bob want to modify 1.hs may be Bob does not like the type (,) in 1.hs Bob has Vector_2.hs module Vector_2 where data Vector_2 a b = C a b x1_of :: Vector_2 a b -> a x1_of ( C x1 _ ) = x1 x2_of :: Vector_2 a b -> b x2_of ( C _ x2 ) = x2 Bob like his Vector_2.hs Bob thinks the Vector_2 shall be good enough to replace (,) in 1.hs i want to create a translator.hs for Bob Bob tell the translator.hs that Bob want to replace (,) with Vector_2 in 1.hs translator.hs automatically translate 1.hs to 2.hs 2.hs shall look like this import Vector_2 ( Vector_2 ) import qualified Vector_2 v :: Vector_2 Int Bool v = Vector_2.C 0 False main :: IO () main = putStrLn "print some magic number" >> print ( Vector_2.x1_of v ) what shall i do ?

The term for this is "automatic refactoring". It's a deep problem, but it's been written about a lot. On Wed, May 24, 2023 at 7:53 AM profited--- via Haskell-Cafe < haskell-cafe@haskell.org> wrote:
let's consider this example Alice has 1.hs like this v :: (,) Int Bool v = (,) 0 False
main :: IO () main = putStrLn "print some magic number" >> print ( fst v )
Bob download 1.hs from Alice
Bob would like to change 1.hs to 2.hs Bob want the programs [ 1.hs 2.hs ] to behave the same
the reason that Bob want to modify 1.hs may be Bob does not like the type (,) in 1.hs
Bob has Vector_2.hs module Vector_2 where
data Vector_2 a b = C a b
x1_of :: Vector_2 a b -> a x1_of ( C x1 _ ) = x1
x2_of :: Vector_2 a b -> b x2_of ( C _ x2 ) = x2
Bob like his Vector_2.hs Bob thinks the Vector_2 shall be good enough to replace (,) in 1.hs
i want to create a translator.hs for Bob Bob tell the translator.hs that Bob want to replace (,) with Vector_2 in 1.hs translator.hs automatically translate 1.hs to 2.hs 2.hs shall look like this import Vector_2 ( Vector_2 ) import qualified Vector_2
v :: Vector_2 Int Bool v = Vector_2.C 0 False
main :: IO () main = putStrLn "print some magic number" >> print ( Vector_2.x1_of v )
what shall i do ? _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
-- Jeff Brown | Jeffrey Benjamin Brown LinkedIn https://www.linkedin.com/in/jeffreybenjaminbrown | Github https://github.com/jeffreybenjaminbrown | Twitter https://twitter.com/carelogic | Facebook https://www.facebook.com/mejeff.younotjeff

I don't think that's possible. Assume that there is a library that contains a module Stupid with a function osiudfhg, which is actually the same as fst: module Stupid where osiudfhg :: (a, b) -> a osiudfhg (a, _) = a If Alice uses that library, then her code could look like main = putStrLn "print some magic number" >> print ( osiudfhg v ) How is Bob's code supposed to look? Maybe it should somehow replace "osiudfhg" with "x1_of", but how is it supposed to know that? It is a library function, after all. Yes, it might analyze source code of the Stupid module, but this is a daunting task.
On 24 May 2023, at 14:52, profited--- via Haskell-Cafe
wrote: let's consider this example Alice has 1.hs like this v :: (,) Int Bool v = (,) 0 False
main :: IO () main = putStrLn "print some magic number" >> print ( fst v )
Bob download 1.hs from Alice
Bob would like to change 1.hs to 2.hs Bob want the programs [ 1.hs 2.hs ] to behave the same
the reason that Bob want to modify 1.hs may be Bob does not like the type (,) in 1.hs
Bob has Vector_2.hs module Vector_2 where
data Vector_2 a b = C a b
x1_of :: Vector_2 a b -> a x1_of ( C x1 _ ) = x1
x2_of :: Vector_2 a b -> b x2_of ( C _ x2 ) = x2
Bob like his Vector_2.hs Bob thinks the Vector_2 shall be good enough to replace (,) in 1.hs
i want to create a translator.hs for Bob Bob tell the translator.hs that Bob want to replace (,) with Vector_2 in 1.hs translator.hs automatically translate 1.hs to 2.hs 2.hs shall look like this import Vector_2 ( Vector_2 ) import qualified Vector_2
v :: Vector_2 Int Bool v = Vector_2.C 0 False
main :: IO () main = putStrLn "print some magic number" >> print ( Vector_2.x1_of v )
what shall i do ? _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Maybe it should somehow replace "osiudfhg" with "x1_of", but how is it supposed to know that? It is a library function, after all.
My understanding was that the user would ask for a refactoring by
explaining the isomorphism between two data types.
I just remembered that Facebook open-sourced something called Retrie that
they use to refactor their own Haskell code. That should give a solid lower
bound on what is possible.
On Wed, May 24, 2023 at 8:02 AM MigMit
I don't think that's possible. Assume that there is a library that contains a module Stupid with a function osiudfhg, which is actually the same as fst:
module Stupid where osiudfhg :: (a, b) -> a osiudfhg (a, _) = a
If Alice uses that library, then her code could look like
main = putStrLn "print some magic number" >> print ( osiudfhg v )
How is Bob's code supposed to look? Maybe it should somehow replace "osiudfhg" with "x1_of", but how is it supposed to know that? It is a library function, after all.
Yes, it might analyze source code of the Stupid module, but this is a daunting task.
On 24 May 2023, at 14:52, profited--- via Haskell-Cafe < haskell-cafe@haskell.org> wrote:
let's consider this example Alice has 1.hs like this v :: (,) Int Bool v = (,) 0 False
main :: IO () main = putStrLn "print some magic number" >> print ( fst v )
Bob download 1.hs from Alice
Bob would like to change 1.hs to 2.hs Bob want the programs [ 1.hs 2.hs ] to behave the same
the reason that Bob want to modify 1.hs may be Bob does not like the type (,) in 1.hs
Bob has Vector_2.hs module Vector_2 where
data Vector_2 a b = C a b
x1_of :: Vector_2 a b -> a x1_of ( C x1 _ ) = x1
x2_of :: Vector_2 a b -> b x2_of ( C _ x2 ) = x2
Bob like his Vector_2.hs Bob thinks the Vector_2 shall be good enough to replace (,) in 1.hs
i want to create a translator.hs for Bob Bob tell the translator.hs that Bob want to replace (,) with Vector_2 in 1.hs translator.hs automatically translate 1.hs to 2.hs 2.hs shall look like this import Vector_2 ( Vector_2 ) import qualified Vector_2
v :: Vector_2 Int Bool v = Vector_2.C 0 False
main :: IO () main = putStrLn "print some magic number" >> print ( Vector_2.x1_of v )
what shall i do ? _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
-- Jeff Brown | Jeffrey Benjamin Brown LinkedIn https://www.linkedin.com/in/jeffreybenjaminbrown | Github https://github.com/jeffreybenjaminbrown | Twitter https://twitter.com/carelogic | Facebook https://www.facebook.com/mejeff.younotjeff

It seems to me that when you have an isomorphism between two types, a natural transformation from one to the other would usually be included in whichever of the two types are the newer (or maybe both). For example, Vector_2 would have e.g. fromTuple :: (a, b) -> Vector_2 a b fromTuple (a, b) = C a b toTuple :: Vactor_2 a b -> (a, b) toTuple (C a b) = (a, b) then in the interim, one could use these to interface between them. When types and natural transformation functions like these exist in scope, text editor plugins should be able to take advantage of these using parsers such as happy/alex/ghc's/hlint. I've used specifically hlint rules to rewrite, maybe that will help for now? Cheers
participants (4)
-
Dan Dart
-
Jeffrey Brown
-
MigMit
-
profited@tutanota.com