]> Git — Sourcephile - haskell/symantic.git/blob - Language/Symantic/Type/Ordering.hs
init
[haskell/symantic.git] / Language / Symantic / Type / Ordering.hs
1 {-# LANGUAGE FlexibleContexts #-}
2 {-# LANGUAGE GADTs #-}
3 {-# LANGUAGE MultiParamTypeClasses #-}
4 {-# LANGUAGE OverloadedStrings #-}
5 {-# LANGUAGE ScopedTypeVariables #-}
6 {-# LANGUAGE TypeFamilies #-}
7 module Language.Symantic.Type.Ordering where
8
9 import Data.Maybe (isJust)
10 import Data.Type.Equality ((:~:)(Refl))
11
12 import Language.Symantic.Type.Common
13
14 -- * Type 'Type_Ordering'
15 -- | The 'Ordering' type.
16 data Type_Ordering (root:: * -> *) h where
17 Type_Ordering :: Type_Ordering root Ordering
18 type instance Root_of_Type (Type_Ordering root) = root
19 type instance Error_of_Type ast (Type_Ordering root) = No_Error_Type
20
21 instance -- Eq_Type
22 Eq_Type (Type_Ordering root) where
23 eq_type Type_Ordering Type_Ordering = Just Refl
24 instance -- Eq
25 Eq (Type_Ordering root h) where
26 x == y = isJust $ x `eq_type` y
27 instance -- String_from_Type
28 String_from_Type (Type_Ordering root) where
29 string_from_type Type_Ordering = "Ordering"
30 instance -- Show
31 Show (Type_Ordering root h) where
32 show = string_from_type
33
34 -- | Convenient alias to include a 'Type_Ordering' within a type.
35 type_ordering :: Type_Root_Lift Type_Ordering root => root Ordering
36 type_ordering = type_root_lift Type_Ordering