]> Git — Sourcephile - haskell/symantic.git/blob - Language/Symantic/Type/List.hs
IO, Monoid, Foldable, Text
[haskell/symantic.git] / Language / Symantic / Type / List.hs
1 {-# LANGUAGE FlexibleContexts #-}
2 {-# LANGUAGE FlexibleInstances #-}
3 {-# LANGUAGE MultiParamTypeClasses #-}
4 {-# LANGUAGE PatternSynonyms #-}
5 {-# LANGUAGE TypeFamilies #-}
6 {-# OPTIONS_GHC -fno-warn-orphans #-}
7 module Language.Symantic.Type.List where
8
9 import Data.Proxy
10 import Data.Type.Equality ((:~:)(Refl))
11 import Language.Symantic.Type.Root
12 import Language.Symantic.Type.Type0
13 import Language.Symantic.Type.Type1
14
15 -- * Type 'Type_List'
16 -- | The list type.
17 type Type_List = Type_Type1 (Proxy [])
18
19 pattern Type_List :: root a -> Type_List root ([] a)
20 pattern Type_List a = Type_Type1 Proxy a
21
22 instance Constraint_Type Eq root => Constraint_Type Eq (Type_List root) where
23 constraint_type c (Type_Type1 _ a)
24 | Just Dict <- constraint_type c a
25 = Just Dict
26 constraint_type _c _ = Nothing
27 instance Constraint_Type Ord root => Constraint_Type Ord (Type_List root) where
28 constraint_type c (Type_Type1 _ a)
29 | Just Dict <- constraint_type c a
30 = Just Dict
31 constraint_type _c _ = Nothing
32 instance Constraint_Type Monoid (Type_List root) where
33 constraint_type _c Type_Type1{} = Just Dict
34 instance Constraint_Type1 Functor (Type_List root) where
35 constraint_type1 _c Type_Type1{} = Just Dict
36 instance Constraint_Type1 Applicative (Type_List root) where
37 constraint_type1 _c Type_Type1{} = Just Dict
38 instance Constraint_Type1 Foldable (Type_List root) where
39 constraint_type1 _c Type_Type1{} = Just Dict
40 instance Constraint_Type1 Traversable (Type_List root) where
41 constraint_type1 _c Type_Type1{} = Just Dict
42 instance Constraint_Type1 Monad (Type_List root) where
43 constraint_type1 _c Type_Type1{} = Just Dict
44 instance -- Eq_Type
45 Eq_Type root =>
46 Eq_Type (Type_List root) where
47 eq_type (Type_Type1 _px1 a1) (Type_Type1 _px2 a2)
48 | Just Refl <- a1 `eq_type` a2
49 = Just Refl
50 eq_type _ _ = Nothing
51 instance -- Eq_Type1
52 Eq_Type1 (Type_List root) where
53 eq_type1 Type_Type1{} Type_Type1{}
54 = Just Refl
55 instance -- String_from_Type
56 String_from_Type root =>
57 String_from_Type (Type_List root) where
58 string_from_type (Type_Type1 _f a) =
59 "[" ++ string_from_type a ++ "]"
60
61 -- | Inject 'Type_List' within a root type.
62 type_list
63 :: Lift_Type_Root Type_List root
64 => root h_a
65 -> root ([] h_a)
66 type_list = lift_type_root . Type_Type1 (Proxy::Proxy [])