User Tools

Site Tools


codesnippets:parametrictypeforanintermediatevaluewhencombiningfunctions

Differences

This shows you the differences between two versions of the page.

Link to this comparison view

Next revision
Previous revision
codesnippets:parametrictypeforanintermediatevaluewhencombiningfunctions [2021/04/23 18:40] – created f2b216codesnippets:parametrictypeforanintermediatevaluewhencombiningfunctions [2025/10/08 00:48] (current) – external edit 127.0.0.1
Line 1: Line 1:
-====== Type for an intermediate value when combining functions ======+====== Parametric type for an intermediate value when combining functions ======
  
   * example with the folling problem(s):   * example with the folling problem(s):
-    * function ''buildNRender'' has an ambigious intermediate type+    * function ''buildNRender'' has an ambigious intermediate parametric type 
 +    * the type of ''buildNRender'' has no parametric type g involved at all 
 +      * hence, it does not make sense to have ''buildNRender'' as a member of ''class'' ''Builder'' 
     * code <code Haskell>     * code <code Haskell>
 module Main where module Main where
Line 28: Line 30:
     build s = Contains (MyData (read s :: Integer))     build s = Contains (MyData (read s :: Integer))
     render (Contains (MyData n)) = Oct.toOctets n     render (Contains (MyData n)) = Oct.toOctets n
-    render (Error _) = []</code> +    render (Error _) = [] 
-  * example that solves the problem+</code> 
 +    * compiles, with error:<code> 
 +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] 
 +       ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ 
 +</code> 
 +  * example that solves the problem with extensions
     * code <code Haskell>     * code <code Haskell>
 {-# LANGUAGE AllowAmbiguousTypes, TypeApplications, ScopedTypeVariables #-} {-# LANGUAGE AllowAmbiguousTypes, TypeApplications, ScopedTypeVariables #-}
Line 62: Line 82:
     render (Error _) = []     render (Error _) = []
 </code> </code>
 +  * example that solves the problem with proxy passing
 +    * NOTE: Proxy has a type parameter that is not used and does not even carry data.
 +    * code <code Haskell>
 +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
 +</code>
 +  * example that solves the problem with Tagged
 +    * NOTE: Proxy has a type parameter that is not used and does not even carry data.
 +    * code <code Haskell>
 +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 _) = []
 +</code>
 +
 +
 +===== ✎ =====
 +~~DISCUSSION~~
codesnippets/parametrictypeforanintermediatevaluewhencombiningfunctions.1619196004.txt.gz · Last modified: (external edit)

Except where otherwise noted, content on this wiki is licensed under the following license: CC0 1.0 Universal
CC0 1.0 Universal Donate Powered by PHP Valid HTML5 Valid CSS Driven by DokuWiki