Dispatch on implemented instances

Hello, everyone! I want to call one function (or the same but with a special argument, no matter) if a type instantiates some type-class or another - if not. I know that it's easy in languages like D, Java, possible C++ - we can specialize templates more generic or less generic and to restrict its parameters with class/interface implementation/extending (there are special keywords/type operators for it, used in generics/templates signatures). So, I suppose Haskell can do the same. But as it turned out, this is not so easy for Haskell :( I found these useful links: * https://stackoverflow.com/questions/26303353/can-multiple-dispatch-be-achiev... * https://wiki.haskell.org/GHC/AdvancedOverlap So, I wrote something like this (this example is compiling and works as I expect, you need `mustache` and `network-uri` packages). Goal is to substitute type in special way for HTML template and for text template if type implements a special interface (for deterministic substitution). Otherwise default substitution will be used. Actually, this code allows usage of not only HTML/text templates... OK, here it is: {-# LANGUAGE EmptyDataDecls #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE UndecidableInstances #-} import Data.Semigroup ((<>)) import qualified Data.Text as T import Network.URI import qualified Text.Mustache.Types as MUT type Link = (T.Text, URI) -- caption and URL, for example -- |Converts a type to substitutable to Mustache template entity based on 'SubTo' template selector. -- @sub@ must be ignored in implementation class ToMustaches sub a where toMustaches :: sub -> a -> SubTo -> MUT.Value -- |Substituted to HTML either to text data SubTo = ToHtml | ToText -- |Deterministic substitution data DetSub -- |Universal substitution data UniSub -- |Substitution predicate: it's determined uniquely for type class SubPred a sub | a -> sub -- TODO rename ToMustaches' (ToMustaches' ?) class ToMustaches' a where toMustaches' :: a -> SubTo -> MUT.Value instance (SubPred a sub, ToMustaches sub a) => ToMustaches' a where toMustaches' a to = toMustaches (undefined::sub) a to -- See: -- * https://stackoverflow.com/questions/36913922/how-to-resolve-overlapping-inst... -- * https://stackoverflow.com/questions/26303353/can-multiple-dispatch-be-achiev... instance {-# OVERLAPS #-} (sub ~ UniSub) => SubPred a sub -- 'Link' can be substituted deterministically instance SubPred Link DetSub instance ToMustaches DetSub Link where toMustaches _ (_, url) ToText = MUT.String $ T.pack $ show url toMustaches _ (cap, url) ToHtml = MUT.String (" (T.pack $ show url) <> "\">" <> cap <> "</a>") -- |All other types which does not implements 'ToMustaches' default instance transforms them to string w/ 'Show' instance Show a => ToMustaches UniSub a where toMustaches _ a _ = MUT.String $ T.pack $ show a ------------------------------------------------------------------- main :: IO () main = do let uri = URI "http:" (Just $ URIAuth "" "wikipedia.org" "") "" "" "" lnk = ("wikipedia", uri)::Link txt = "Hello world"::T.Text n = 444::Int print $ toMustaches' lnk ToText print $ toMustaches' lnk ToHtml print $ toMustaches' txt ToHtml print $ toMustaches' n ToText I don't know am I understand correctly the Haskell solution but this looks close to explained in the Haskell Wiki (case 1). But in all cases I see problem: always I need not only to implement this special interface but to "say" that a type implements special (deterministic) substitution, see: instance SubPred Link DetSub This means that clients of this code must "implements" 2 instances: 1) of ToMustaches and 2) of SubPred (with DetSub as last type param). This is terrible and no such thing in other languages! So, my question is: is a simple way to avoid it? === Best regards, Paul
participants (1)
-
PY