NLinker

Making js code equivalent

Mar 26th, 2019
378
0
Never
Not a member of Pastebin yet? Sign Up, it unlocks many cool features!

JS

function add(x, y) { return x + y; }

function main() {
  var a = 1, b = "hello";
  console.log(add(a, b));
}

Haskell, variant 1

Just explicit call with explicit type conversions:

main = do
    let x = 1
    let y = "hello"
    putStrLn $ show x ++ y

Haskell, variant 2

Extract the expression into the function with the concrete type

add :: String -> String -> String
add x y = x ++ y

main = do
    let x = 1
    let y = "hello"
    putStrLn $ add (show x) y

Haskell, variant 3

Generalize the function add:

import Data.Monoid ((<>))

add :: Monoid m => m -> m -> m
add x y = x <> y

main = do
    let x = 1
    let y = "hello"
    putStrLn $ add (show x) y

Haskell, variant 4

Make the add function to be part of a type class, so we can get rid of the explicit show function call:

{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}

import Data.Monoid ((<>))

class Addable a b c | a b -> c where
    add :: a -> b -> c
instance Addable Integer String String where
    add a b = show a <> b
instance Addable String Integer String where
    add a b = a <> show b

-- add :: (Monoid m) => m -> m -> m
-- add x y = x <> y

main = do
    let x = 1
    let y = "hello"
    putStrLn $ add x y

Haskell, variant 5

Make the add function polymorphic in another way:

import Data.Monoid ((<>))

add :: (Show s1, Show s2) => s1 -> s2 -> String
add x y = show x <> show y

main = do
    let x = 1
    let y = "hello"
    putStrLn $ add x y

Haskell, variant 6

Make some universal wrapper type, that we can wrap integers or strings in. Then define add function over the wrapper types:

{-# LANGUAGE FlexibleInstances #-}

import Data.Monoid ((<>))
import Data.String (IsString(..))

data Wrap = S String | I Integer

class Wrappable a where
    wrap :: a -> Wrap

instance Wrappable Integer where
    wrap = I

instance Wrappable String where
    wrap = S

instance Show Wrap where
    show (S s) = s
    show (I x) = show x

add :: Wrap -> Wrap -> Wrap
add x y = S $ tos x <> tos y
    where
        tos (I x) = show x
        tos (S s) = s

main = do
    let x = wrap (1 :: Integer)
    let y = wrap "hello"
    putStrLn $ show $ add x y
Add Comment
Please, Sign In to add comment