]> Git — Sourcephile - haskell/symantic.git/blob - Language/Symantic/Type/List.hs
MonoFunctor
[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 qualified Data.MonoTraversable as MT
10 import Data.Proxy
11 import Data.Type.Equality ((:~:)(Refl))
12 import Language.Symantic.Type.Root
13 import Language.Symantic.Type.Type0
14 import Language.Symantic.Type.Type1
15
16 -- * Type 'Type_List'
17 -- | The list type.
18 type Type_List = Type_Type1 (Proxy [])
19
20 pattern Type_List :: root a -> Type_List root ([] a)
21 pattern Type_List a = Type_Type1 Proxy a
22
23 instance Constraint_Type Eq root => Constraint_Type Eq (Type_List root) where
24 constraint_type c (Type_Type1 _ a)
25 | Just Dict <- constraint_type c a
26 = Just Dict
27 constraint_type _c _ = Nothing
28 instance Constraint_Type Ord root => Constraint_Type Ord (Type_List root) where
29 constraint_type c (Type_Type1 _ a)
30 | Just Dict <- constraint_type c a
31 = Just Dict
32 constraint_type _c _ = Nothing
33 instance Constraint_Type Monoid (Type_List root) where
34 constraint_type _c Type_Type1{} = Just Dict
35 instance Constraint_Type Num (Type_List root)
36 instance Constraint_Type Integral (Type_List root)
37 instance Constraint_Type MT.MonoFunctor (Type_List root) where
38 constraint_type _c Type_Type1{} = Just Dict
39 instance Constraint_Type1 Functor (Type_List root) where
40 constraint_type1 _c Type_Type1{} = Just Dict
41 instance Constraint_Type1 Applicative (Type_List root) where
42 constraint_type1 _c Type_Type1{} = Just Dict
43 instance Constraint_Type1 Foldable (Type_List root) where
44 constraint_type1 _c Type_Type1{} = Just Dict
45 instance Constraint_Type1 Traversable (Type_List root) where
46 constraint_type1 _c Type_Type1{} = Just Dict
47 instance Constraint_Type1 Monad (Type_List root) where
48 constraint_type1 _c Type_Type1{} = Just Dict
49 instance -- Eq_Type
50 Eq_Type root =>
51 Eq_Type (Type_List root) where
52 eq_type (Type_Type1 _px1 a1) (Type_Type1 _px2 a2)
53 | Just Refl <- a1 `eq_type` a2
54 = Just Refl
55 eq_type _ _ = Nothing
56 instance -- Eq_Type1
57 Eq_Type1 (Type_List root) where
58 eq_type1 Type_Type1{} Type_Type1{}
59 = Just Refl
60 instance -- String_from_Type
61 String_from_Type root =>
62 String_from_Type (Type_List root) where
63 string_from_type (Type_Type1 _f a) =
64 "[" ++ string_from_type a ++ "]"
65
66 -- | Inject 'Type_List' within a root type.
67 type_list
68 :: Lift_Type_Root Type_List root
69 => root h_a
70 -> root ([] h_a)
71 type_list = type_type1