Created
May 8, 2021 14:57
-
-
Save guibou/6d10bc936f446c7c24f2ca3423f5e05a to your computer and use it in GitHub Desktop.
Define a small expression language, which overload Num and Fractional (And perhaps other types) and works correctly with defaulting.
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
| {-# LANGUAGE TypeApplications #-} | |
| {-# LANGUAGE MultiParamTypeClasses #-} | |
| {-# LANGUAGE FunctionalDependencies #-} | |
| {-# LANGUAGE FlexibleInstances #-} | |
| {-# LANGUAGE TypeFamilies #-} | |
| {-# LANGUAGE AllowAmbiguousTypes #-} | |
| {-# LANGUAGE ScopedTypeVariables #-} | |
| f :: Num a => a -> a -> a | |
| f x y = x * y | |
| g :: Num a => a -> a | |
| g x = negate x | |
| data Unop = Negate | Abs | Signum | FromInteger | Inv | |
| deriving (Show) | |
| data Binop = Add | Mul | Sub | Div | |
| deriving (Show) | |
| instance Num n => Num (Expr a n) where | |
| (+) = Binop Add | |
| (*) = Binop Mul | |
| abs = Unop Abs | |
| signum = Unop Signum | |
| fromInteger i = K (fromInteger i) | |
| (-) = Binop Sub | |
| negate = Unop Negate | |
| instance Fractional a => Fractional (Expr v a) where | |
| fromRational = K . fromRational | |
| recip = Unop Inv | |
| (/) = Binop Div | |
| data Expr v a = K a | V v | Unop Unop (Expr v a) | Binop Binop (Expr v a) (Expr v a) | |
| deriving (Show) | |
| class Exprify p v e where | |
| exprify' :: v -> e -> (Expr v p, v) | |
| instance Exprify a v (Expr v a) where | |
| exprify' i e = (e, i) | |
| instance (Enum v, Num a, b ~ Expr v a, Exprify a v c) => Exprify a v (b -> c) where | |
| exprify' i f = exprify' (succ i) (f (V i)) | |
| a :: Expr v Float | |
| a = K pi | |
| compile :: forall p e v. (Show v, Show p, Exprify p v e) => v -> e -> String | |
| compile s e = show (exprify' @p @v s e) |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment