{-# LANGUAGE OverloadedStrings #-} {-# OPTIONS_GHC -fno-warn-orphans #-} module Language.LOL.Typing.Expr.Write where import Data.Maybe (Maybe(..)) import Data.Monoid ((<>)) import Data.Text.Buildable (Buildable(..)) import Language.LOL.Typing.Expr.Grammar instance Buildable Expr where build expr = case expr of Expr_Var nam -> build nam Expr_App f x -> "(" <> build f <> " " <> build x <> ")" Expr_Annot e sig -> "(" <> build e <> " : " <> build sig <> ")" Expr_Let sig nam decl e -> "let " <> n <> " = " <> build decl <> " in " <> build e where n = case sig of Just s -> "("<>build nam<>":"<>build s<>")" Nothing -> build nam Expr_Where sig nam decl e -> build e <> " where " <> n <> " = " <> build decl where n = case sig of Just s -> "("<>build nam<>":"<>build s<>")" Nothing -> build nam Expr_Abst sig nam e -> "(" <> "\\" <> n <> " -> " <> build e <> ")" where n = case sig of Just s -> "("<>build nam<>":"<>build s<>")" Nothing -> build nam instance Buildable Decl where build decl = case decl of Decl_Let sig nam expr -> n <> " = " <> build expr where n = case sig of Just s -> "("<>build nam<>":"<>build s<>")" Nothing -> build nam