Skip to content

Instantly share code, notes, and snippets.

@chrisnc
Last active August 29, 2015 14:12
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save chrisnc/10f3728c13096b2c5487 to your computer and use it in GitHub Desktop.
Save chrisnc/10f3728c13096b2c5487 to your computer and use it in GitHub Desktop.
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE FlexibleInstances #-}
module Literals
( eval
, env
, expr
, main
) where
import Data.String
import Data.Map (Map)
import qualified Data.Map as Map
import Control.Applicative
type Env a = Map String a
type Expr a = Map String a -> a
instance IsString (Expr a) where
fromString s =
Map.findWithDefault
(error ("the variable " ++ s ++ " was not defined"))
s
instance (Applicative f, Num a) => Num (f a) where
(+) = liftA2 (+)
(*) = liftA2 (*)
(-) = liftA2 (-)
negate = fmap negate
abs = fmap abs
signum = fmap signum
fromInteger = pure . fromInteger
instance (Applicative f, Fractional a) => Fractional (f a) where
(/) = liftA2 (/)
recip = fmap recip
fromRational = pure . fromRational
-- for type inference in the repl
-- example:
-- eval ("a" + "b") env -- works
-- ("a" + "b") env -- can't unify
eval :: Expr a -> Env a -> a
eval = ($)
env :: Num a => Env a
env = Map.fromList [("a",3), ("b",4), ("c",7)]
expr :: Fractional a => Expr a
expr = (3 * "a" + 2 * "b" + 5 * "c") / 2.0 + 1
main :: IO ()
main = print (expr env :: Double)
@chrisnc
Copy link
Author

chrisnc commented Dec 30, 2014

An example of using Haskell's polymorphic string and numeric literals to make a simple expression type, using string literals as symbolic variables. Both numeric literals and string literals are given the type
Map String a -> a, and can be combined using the Num (and Fractional) typeclass over Applicative.

@chrisnc
Copy link
Author

chrisnc commented Dec 30, 2014

If you want to use this in GHCi, you will need to do :set -XOverloadedStrings first, otherwise any symbolic variables you use will be defaulted to String.

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment