]> Git — Sourcephile - haskell/symantic.git/blob - Language/Symantic/Expr/Int.hs
factorizing Type1_From ast Type0
[haskell/symantic.git] / Language / Symantic / Expr / Int.hs
1 {-# LANGUAGE DefaultSignatures #-}
2 {-# LANGUAGE FlexibleContexts #-}
3 {-# LANGUAGE ScopedTypeVariables #-}
4 {-# LANGUAGE TypeFamilies #-}
5 {-# LANGUAGE TypeOperators #-}
6 -- | Expression for 'Int'.
7 module Language.Symantic.Expr.Int where
8
9 import Data.Proxy
10 import qualified Data.Text as Text
11
12 import Language.Symantic.Type
13 import Language.Symantic.Repr
14 import Language.Symantic.Expr.Root
15 import Language.Symantic.Expr.Error
16 import Language.Symantic.Expr.From
17 import Language.Symantic.Trans.Common
18
19 -- * Class 'Sym_Int'
20 -- | Symantic.
21 class Sym_Int repr where
22 int :: Int -> repr Int
23 default int :: Trans t repr => Int -> t repr Int
24 int = trans_lift . int
25 instance Sym_Int Repr_Host where
26 int = Repr_Host
27 instance Sym_Int Repr_Text where
28 int a = Repr_Text $ \_p _v ->
29 Text.pack (show a)
30 instance (Sym_Int r1, Sym_Int r2) => Sym_Int (Repr_Dup r1 r2) where
31 int x = int x `Repr_Dup` int x
32
33 sym_Int :: Proxy Sym_Int
34 sym_Int = Proxy
35
36 -- * Type 'Expr_Int'
37 -- | Expression.
38 data Expr_Int (root:: *)
39 type instance Root_of_Expr (Expr_Int root) = root
40 type instance Type_of_Expr (Expr_Int root) = Type_Int
41 type instance Sym_of_Expr (Expr_Int root) repr = Sym_Int repr
42 type instance Error_of_Expr ast (Expr_Int root) = No_Error_Expr