]> Git — Sourcephile - haskell/symantic.git/blob - symantic-grammar/Language/Symantic/Grammar/Source.hs
grammar: rename At -> Sourced
[haskell/symantic.git] / symantic-grammar / Language / Symantic / Grammar / Source.hs
1 {-# LANGUAGE DeriveFunctor #-}
2 {-# LANGUAGE TypeFamilies #-}
3 module Language.Symantic.Grammar.Source where
4
5 import Data.Eq (Eq)
6 import Data.Ord (Ord)
7 import Text.Show (Show)
8 import Data.Functor (Functor)
9 import Data.Typeable (Typeable)
10
11 -- * Class 'Source'
12 class Source src where
13 noSource :: src
14 instance Source () where
15 noSource = ()
16
17 -- ** Class 'SourceInj'
18 class Source src => SourceInj a src where
19 sourceInj :: a -> src
20 instance SourceInj a () where
21 sourceInj _ = ()
22
23 -- ** Type family 'SourceOf'
24 type family SourceOf a
25
26 -- ** Type 'Sourceable'
27 class Source (SourceOf a) => Sourceable a where
28 sourceOf :: a -> SourceOf a
29 setSource :: a -> SourceOf a -> a
30 infixl 5 `setSource`
31
32 withSource :: SourceInj src (SourceOf a) => Sourceable a => a -> src -> a
33 withSource a src = a `setSource` sourceInj src
34
35 -- ** Type 'Source_Input'
36 type family Source_Input (src :: *) :: *
37 type instance Source_Input () = ()
38
39 -- ** Type 'Span'
40 data Span src
41 = Span
42 { spanBegin :: !src
43 , spanEnd :: !src
44 } deriving (Eq, Ord, Show, Typeable)
45
46 -- ** Type 'Sourced'
47 -- | Attach a 'Source' to something.
48 data Sourced src a
49 = Sourced
50 { atSource :: !src
51 , unSourced :: !a
52 } deriving (Eq, Functor, Ord, Show, Typeable)