buildNRender has an ambigious intermediate parametric typebuildNRender has no parametric type g involved at allbuildNRender as a member of class Builder module Main where import qualified Data.Word as W import qualified Octetable as Oct main :: IO () main = do print (buildNRender "123") data MyData = MyData Integer data Construction model = Contains model | Error String deriving Show class Builder g where build :: String -> (Construction g) render :: (Construction g) -> [W.Word8] buildNRender :: String -> [W.Word8] buildNRender = render . build instance Builder MyData where build s = Contains (MyData (read s :: Integer)) render (Contains (MyData n)) = Oct.toOctets n render (Error _) = []
app\Main.hs:19:5: error:
* Could not deduce (Builder g0)
from the context: Builder g
bound by the type signature for:
buildNRender :: forall g. Builder g => String -> [W.Word8]
at app\Main.hs:19:5-39
The type variable `g0' is ambiguous
* In the ambiguity check for `buildNRender'
To defer the ambiguity check to use sites, enable AllowAmbiguousTypes
When checking the class method:
buildNRender :: forall g. Builder g => String -> [W.Word8]
In the class declaration for `Builder'
|
19 | buildNRender :: String -> [W.Word8]
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
{-# LANGUAGE AllowAmbiguousTypes, TypeApplications, ScopedTypeVariables #-} module Main where import qualified Data.Word as W import qualified Octetable as Oct main :: IO () main = do print (buildNRender @MyData "123") data MyData = MyData Integer data Construction model = Contains model | Error String deriving Show class Builder g where build :: String -> (Construction g) render :: (Construction g) -> [W.Word8] buildNRender :: forall g . Builder g => String -> [W.Word8] -- forall g . introduces the Scope of Type Variable g -- needs extension AllowAmbiguousTypes buildNRender = render . build @g -- @g is a Type Application instance Builder MyData where build s = Contains (MyData (read s :: Integer)) render (Contains (MyData n)) = Oct.toOctets n render (Error _) = []
module Main where import qualified Data.Word as W import qualified Octetable as Oct main :: IO () main = do print (buildNRender (Proxy :: Proxy MyData) "123") data MyData = MyData Integer data Construction model = Contains model | Error String deriving Show class Builder g where build :: String -> (Construction g) render :: (Construction g) -> [W.Word8] buildNRender :: proxy g -> String -> [W.Word8] buildNRender p = render . applyProxy p build where applyProxy :: proxy g -> f (c g) -> f (c g) applyProxy _ = id instance Builder MyData where build s = Contains (MyData (read s :: Integer)) render (Contains (MyData n)) = Oct.toOctets n render (Error _) = [] data Proxy a = Proxy
module Main where import qualified Data.Word as W import qualified Octetable as Oct import qualified Data.Tagged as Tg main :: IO () main = do print ((getTaggedFunc (buildNRender :: Tg.Tagged MyData (String -> [W.Word8]))) "123") getTaggedFunc :: Tg.Tagged g (String -> [W.Word8]) -> (String -> [W.Word8]) getTaggedFunc (Tg.Tagged f) = f data MyData = MyData Integer data Construction model = Contains model | Error String deriving Show class Builder g where build :: String -> (Construction g) render :: (Construction g) -> [W.Word8] buildNRender :: Tg.Tagged g (String -> [W.Word8]) buildNRender = (render .) <$> applyTag build where applyTag :: f (c g) -> Tg.Tagged g (f (c g)) applyTag = Tg.Tagged instance Builder MyData where build s = Contains (MyData (read s :: Integer)) render (Contains (MyData n)) = Oct.toOctets n render (Error _) = []