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