Skip to content

Instantly share code, notes, and snippets.

@fredyr
Created August 29, 2014 08:07
Show Gist options
  • Save fredyr/20ff0b4371b42b2cf3f6 to your computer and use it in GitHub Desktop.
Save fredyr/20ff0b4371b42b2cf3f6 to your computer and use it in GitHub Desktop.
{-#LANGUAGE GADTs, KindSignatures, FlexibleInstances, FunctionalDependencies, NoMonomorphismRestriction #-}
-- DOMAIN SPECIFIC LANGUAGES IN HASKELL
-- Fredrik Dyrkell
-- @lexicallyscoped | lexicallyscoped.com
-- DOMAIN SPECIFIC LANGUAGE (DSL)
-- a computer programming language of limited expressiveness focussed
-- on a particular domain (- Martin Fowler)
--
-- A very good paper on Domain Specific Languages in Haskell is:
-- ``FUNCTIONAL PROGRAMMING FOR DOMAIN-SPECIFIC LANGUAGES``
-- by Jeremy Gibbons
--
-- A LITTLE BACKGROUND
-- Two main approaches to implementing DSLs
-- 1. Stand-alone language
-- - Custom syntax, that can be tailored for the domain
-- - Requires building parser, compiler etc -> Significant work
-- 2. Embedded DSL
-- - Leverages syntax and abstractions from a host language
-- - The DSL is a library defining the domain specific semantic
-- - Blurres the boundary between the host and DSL
--
-- We're going to look at a specific form called `deeply embedded` DSL
-- so called because terms in the DSL are implemented simply to
-- construct and abstract syntax tree (AST)
--
-- Using Haskells Algebraic Datatypes(ADT) we can create ASTs like so
-- http://en.wikipedia.org/wiki/Algebraic_data_type
data DExp = LitInt Int
| Add DExp DExp
| Sub DExp DExp
| Mul DExp DExp
| LitBool Bool
deriving Show
-- A value of the DExp type can be created with one of the above
-- `constructor functions`, for example the cf LitInt takes an Integer
-- as argument
-- > LitInt 5
-- > :t LitInt => LitInt :: Int -> DExp
-- > Add (LitInt 4) (LitInt 12)
-- > :t LitBool True
-- Use functions and/or operators for construction
-- The Num type class
-- > :i Num
instance Num DExp where
a + b = Add a b
a - b = Sub a b
a * b = Mul a b
fromInteger i = LitInt $ fromInteger i
-- > 1+4*9 :: DExp
-- > Mul 4 5
sqr x = x * x
conjugate a b = sqr a - sqr b
-- > sqr 4
-- > sqr 4 :: DExp
-- > sqr $ 1+4*9 :: DExp
-- > conjugate (9*3) (4-1)
-- This DSL is `unityped` - everything is DExp, which means its
-- possible to construct illegal ASTs
-- > Mul (LitBool True) 1
-- INTERPRET ALL THE THINGS
-- Pattern match on the different constructor functions and voila
eval :: DExp -> Int
eval (LitInt a) = a
eval (Add a b) = (eval a) + (eval b)
eval (Sub a b) = (eval a) - (eval b)
eval (Mul a b) = (eval a) * (eval b)
-- > eval (LitInt 4)
-- > eval (2+6*4 :: DExp)
-- > eval (conjugate (9*7) (4-2) :: DExp)
-- But you can just as easily
--
-- COMPILE ALL THE THINGS
--
data Asm = Push Int | StackAdd | StackSub | StackMul
deriving Show
genByteCode :: DExp -> [Asm]
genByteCode (LitInt a) = [Push a]
genByteCode (Add a b) = (genByteCode a) ++ (genByteCode b) ++ [StackAdd]
genByteCode (Sub a b) = (genByteCode a) ++ (genByteCode b) ++ [StackSub]
genByteCode (Mul a b) = (genByteCode a) ++ (genByteCode b) ++ [StackMul]
-- > genByteCode (12 + sqr 4 -sqr 2 * 3)
-- > genByteCode $ conjugate (9*7) (4-2)
--
-- SWITCHING GEARS A LITTLE BIT
--
-- Has anybody here done any assembly language coding?
-- I currently do consulting work for a client working w/ embedded
-- systems. Here I have been introduced to the SHARC processor and its
-- assembly language
-- R0-R15 Fixed point (Integer)
-- F0-F15 Floating point
-- Algebraic notation
-- R1 = R2 + R3;
-- F2 = F0 * F1;
-- F9 = MIN(F2, F14)
-- F3 = F2 - F1;
-- With a DSL implementation of the SHARC assembly language you could
-- explore interesting things
-- 1. Faster feedback-loop, since you can run (interpret) code on your
-- machine directly and not run on actual hardware
-- 2. Use Haskell to create abstractions on top of the assembly,
-- advance macros
-- 3. Quickcheck testing and unit testing - Isolation testing an
-- assembly function is a PITA
data Rx = R0 | R1 | R2 | R3 | R4 | R5 | R6 | R7
| R8 | R9 | R10 | R11 | R12 | R13 | R14 | R15
deriving (Show, Eq, Ord)
data Fx = F0 | F1 | F2 | F3 | F4 | F5 | F6 | F7
| F8 | F9 | F10 | F11 | F12 | F13 | F14 | F15
deriving (Show, Eq, Ord)
-- The SHARC asm is strongly typed, you can't mix Rx and Fx registers
-- Illegal examples
-- R2 = R0 + F1
-- F0 = R0 + R1
-- Both the `expression` on the rhs must be correctly typed, as well
-- as the assignment
-- We want the AST to only contain *legal* constructions
-- This is possible using Generalized Algebraic Data Types (GADTs)
-- Expr is now a polymorpic type, but *only* provides constructor
-- functions for Expr Integer and Expr Float and not for other
-- instances of the polymorphic type `Expr a`
data Expr :: * -> * where
LiteralInt :: Integer -> Expr Integer
AddR :: Rx -> Rx -> Expr Integer
LiteralFloat :: Float -> Expr Float
AddF :: Fx -> Fx -> Expr Float
-- > :t LiteralInt 3
-- > :t LiteralFloat 4.9
-- > :t AddF F0 F1
-- > :t AddF F0 R1
-- SHORT DEMO OF THE SHARC ASM DSL
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment