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.IO where
10 import Data.Type.Equality ((:~:)(Refl))
11 import qualified System.IO as IO
12 import Language.Symantic.Type.Root
13 import Language.Symantic.Type.Type0
14 import Language.Symantic.Type.Type1
18 type Type_IO = Type_Type1 (Proxy IO)
19 type Type_IO_Handle = Type_Type0 (Proxy IO.Handle)
20 type Type_IO_FilePath = Type_Type0 (Proxy IO.FilePath)
21 type Type_IO_Mode = Type_Type0 (Proxy IO.IOMode)
23 pattern Type_IO :: root a -> Type_IO root (IO a)
24 pattern Type_IO a = Type_Type1 Proxy a
26 instance Constraint_Type1 Functor (Type_IO root) where
27 constraint_type1 _c Type_Type1{} = Just Dict
28 instance Constraint_Type1 Applicative (Type_IO root) where
29 constraint_type1 _c Type_Type1{} = Just Dict
30 instance Constraint_Type1 Monad (Type_IO root) where
31 constraint_type1 _c Type_Type1{} = Just Dict
34 Eq_Type (Type_IO root) where
35 eq_type (Type_Type1 _px1 a1) (Type_Type1 _px2 a2)
36 | Just Refl <- a1 `eq_type` a2
40 Eq_Type1 (Type_IO root) where
41 eq_type1 Type_Type1{} Type_Type1{}
43 instance -- String_from_Type
44 String_from_Type root =>
45 String_from_Type (Type_IO root) where
46 string_from_type (Type_Type1 _f a) =
47 "[" ++ string_from_type a ++ "]"
49 -- | Inject 'Type_IO' within a root type.
51 :: Lift_Type_Root Type_IO root
54 type_io = lift_type_root . Type_Type1 (Proxy::Proxy IO)
56 -- | Inject 'Type_IO_Handle' within a root type.
58 :: Lift_Type_Root Type_IO_Handle root
60 type_io_handle = lift_type_root $ Type_Type0 (Proxy::Proxy IO.Handle)
62 -- | Inject 'Type_IO_FilePath' within a root type.
64 :: Lift_Type_Root Type_IO_FilePath root
66 type_io_filepath = lift_type_root $ Type_Type0 (Proxy::Proxy IO.FilePath)
68 -- | Inject 'Type_IO_Mode' within a root type.
70 :: Lift_Type_Root Type_IO_Mode root
72 type_io_mode = lift_type_root $ Type_Type0 (Proxy::Proxy IO.IOMode)