User Tools

Site Tools


codesnippets:parametrictypeforanintermediatevaluewhencombiningfunctions

This is an old revision of the document!


Parametric type for an intermediate value when combining functions

  • example with the folling problem(s):
    • 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
      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 _) = []
  • example that solves the problem with extensions
    • code
      {-# 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 _) = []
  • example that solves the problem without extensions
    • code
      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 . blub p build
              where
                  blub :: proxy g -> f (c g) -> f (c g)
                  blub _ = 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
This website uses cookies. By using the website, you agree with storing cookies on your computer. Also you acknowledge that you have read and understand our Privacy Policy. If you do not agree leave the website.More information about cookies
You could leave a comment if you were logged in.
codesnippets/parametrictypeforanintermediatevaluewhencombiningfunctions.1619294249.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