[Haskell-Cafe] How to deal with looped references inside instances?

{- Hi, I am trying to translate a Java sample with looped references below to Haskell. I've found 2 solutions, but both of them look ugly, because they require a helper class. So I am looking for an advice for best practices on working with looped references in polymorphic types. interface Engine { String showEng(); } class Car<E extends Engine> { int id; E eng; String show() { return "Car with " + eng.showEng(); } int getId() { return id; } } class Steam implements Engine { Car<Steam> car; Stream(Car<Steam> car) { this.car = car; } String showEng() { return "id " + car.getId(); } } Car<Steam> car = new Car<>(); car.id = 42; car.eng = new Stream(car); car.show(); -} {-# LANGUAGE UndecidableInstances #-} -- Fix2 shortcoming class Car c where getId :: c -> Int class Engine e where showEng :: e -> String data SteamEng c = SteamEng c instance (Car c) => Engine (SteamEng c) where showEng (SteamEng c) = "id " ++ show (getId c) {- First solution is via ShowEng class. I don't know how to tell type checker that the type which is got after application of type function is instantiating Engine class?? instance (Engine eng) => Show (Car1 eng) where show (Car1 _ eng) = "Car1 with " ++ showEng eng -} data Car1 eng = Car1 Int (eng (Car1 eng)) class ShowEng f where showEng2 :: (Car a) => f a -> String instance ShowEng SteamEng where showEng2 = showEng {- A side note. Intuitive alternative for ShowEng which is not working! showEng2 = showEng means showEng2 gets Engine, but class HaveEngine f where cast :: (Car a) => f a -> f a instance HaveEngine SteamEng where cast = id ... instance (HaveEngine eng) => Show (Car1 eng) where show (Car1 _ eng) = "Car1 with " ++ (showEng (cast eng)) nor instance (HaveEngine eng) => Show (Car1 eng) where show (Car1 _ eng) = "Car1 with " ++ (showEng eng) -} instance Car (Car1 e) where getId (Car1 id _) = id instance (ShowEng eng) => Show (Car1 eng) where show (Car1 _ eng) = "Car1 with " ++ (showEng2 eng) c1 = Car1 42 (SteamEng c1) {- Second solution is removing argument from engine type parameter. -} data Car0 eng = Car0 Int eng instance Car (Car0 e) where getId (Car0 id _) = id instance (Engine eng) => Show (Car0 eng) where show (Car0 _ eng) = "Car0 with " ++ showEng eng {- in this case I have to avoid infinite type and introducing an extra wrapper and instantiating business logic classes for him. λ c0 = Car0 42 (SteamEng c0) <interactive>:30:6: error: • Occurs check: cannot construct the infinite type: car ~ Car0 (SteamEng car) • In the expression: Car0 (SteamEng c0) In an equation for ‘c0’: c0 = Car0 42 (SteamEng c0) • Relevant bindings include c0 :: car (bound at <interactive>:30:1) -} newtype Fix2 f g = Fix2 (f (g (Fix2 f g))) instance (Show (f (g (Fix2 f g)))) => Show (Fix2 f g) where show (Fix2 a) = show a {- λ c0 = Car0 42 (SteamEng (Fix2 c0)) <interactive>:62:1: error: • No instance for (Car (Fix2 Car0 SteamEng)) arising from a use of ‘print’ • In a stmt of an interactive GHCi command: print it -} instance (Car (f (g (Fix2 f g)))) => Car (Fix2 f g) where getId (Fix2 a) = getId a c0 = Car0 42 (SteamEng (Fix2 c0)) {- Thanks, Daniil -}

Hi, I don’t see any problem there. Why not just a pretty much do a one to one translation? class Engine e where showEng :: e -> String data Car e = Car { getId :: Int , getEng :: e } instance Engine e => Show (Car e) where show this = "Car with " ++ (showEng $ getEng $ this) data Steam = Steam { getCar :: Car Steam } instance Engine Steam where showEng this = "id " ++ (show $ getId $ getCar $ this) car :: Car Steam car = Car 42 $ Steam car And then just call „show car“. The should not be a problem with the looped reference. Greetings Jos Von: Daneel Yaitskov Gesendet: Freitag, 1. Mai 2020 01:33 An: haskell-cafe Betreff: [Haskell-cafe] [Haskell-Cafe] How to deal with looped referencesinside instances? {- Hi, I am trying to translate a Java sample with looped references below to Haskell. I've found 2 solutions, but both of them look ugly, because they require a helper class. So I am looking for an advice for best practices on working with looped references in polymorphic types. interface Engine { String showEng(); } class Car<E extends Engine> { int id; E eng; String show() { return "Car with " + eng.showEng(); } int getId() { return id; } } class Steam implements Engine { Car<Steam> car; Stream(Car<Steam> car) { this.car = car; } String showEng() { return "id " + car.getId(); } } Car<Steam> car = new Car<>(); car.id = 42; car.eng = new Stream(car); car.show(); -} {-# LANGUAGE UndecidableInstances #-} -- Fix2 shortcoming class Car c where getId :: c -> Int class Engine e where showEng :: e -> String data SteamEng c = SteamEng c instance (Car c) => Engine (SteamEng c) where showEng (SteamEng c) = "id " ++ show (getId c) {- First solution is via ShowEng class. I don't know how to tell type checker that the type which is got after application of type function is instantiating Engine class?? instance (Engine eng) => Show (Car1 eng) where show (Car1 _ eng) = "Car1 with " ++ showEng eng -} data Car1 eng = Car1 Int (eng (Car1 eng)) class ShowEng f where showEng2 :: (Car a) => f a -> String instance ShowEng SteamEng where showEng2 = showEng {- A side note. Intuitive alternative for ShowEng which is not working! showEng2 = showEng means showEng2 gets Engine, but class HaveEngine f where cast :: (Car a) => f a -> f a instance HaveEngine SteamEng where cast = id ... instance (HaveEngine eng) => Show (Car1 eng) where show (Car1 _ eng) = "Car1 with " ++ (showEng (cast eng)) nor instance (HaveEngine eng) => Show (Car1 eng) where show (Car1 _ eng) = "Car1 with " ++ (showEng eng) -} instance Car (Car1 e) where getId (Car1 id _) = id instance (ShowEng eng) => Show (Car1 eng) where show (Car1 _ eng) = "Car1 with " ++ (showEng2 eng) c1 = Car1 42 (SteamEng c1) {- Second solution is removing argument from engine type parameter. -} data Car0 eng = Car0 Int eng instance Car (Car0 e) where getId (Car0 id _) = id instance (Engine eng) => Show (Car0 eng) where show (Car0 _ eng) = "Car0 with " ++ showEng eng {- in this case I have to avoid infinite type and introducing an extra wrapper and instantiating business logic classes for him. λ c0 = Car0 42 (SteamEng c0) <interactive>:30:6: error: • Occurs check: cannot construct the infinite type: car ~ Car0 (SteamEng car) • In the expression: Car0 (SteamEng c0) In an equation for ‘c0’: c0 = Car0 42 (SteamEng c0) • Relevant bindings include c0 :: car (bound at <interactive>:30:1) -} newtype Fix2 f g = Fix2 (f (g (Fix2 f g))) instance (Show (f (g (Fix2 f g)))) => Show (Fix2 f g) where show (Fix2 a) = show a {- λ c0 = Car0 42 (SteamEng (Fix2 c0)) <interactive>:62:1: error: • No instance for (Car (Fix2 Car0 SteamEng)) arising from a use of ‘print’ • In a stmt of an interactive GHCi command: print it -} instance (Car (f (g (Fix2 f g)))) => Car (Fix2 f g) where getId (Fix2 a) = getId a c0 = Car0 42 (SteamEng (Fix2 c0)) {- Thanks, Daniil -} _______________________________________________ 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.
participants (2)
-
Daneel Yaitskov
-
Jos Kusiek