1 {-# LANGUAGE UndecidableInstances #-}
2 {-# OPTIONS_GHC -fno-warn-orphans #-}
3 -- | Symantic for the file system.
4 module Hcompta.LCC.Sym.FileSystem where
6 import Control.Applicative (Applicative(..))
8 import Data.Foldable (concat)
9 import Data.Function (($), (.))
10 import Data.Functor (Functor(..), (<$>))
11 import Data.Maybe (Maybe(..))
12 import Data.Type.Equality ((:~:)(Refl))
13 import System.IO (FilePath)
14 import Text.Show (Show(..))
15 import qualified Data.Text as Text
16 import qualified Prelude ()
18 import Language.Symantic.Grammar
19 import Language.Symantic
21 import Hcompta.LCC.Journal (PathFile(..))
23 -- * Class 'Sym_PathFile'
24 type instance Sym PathFile = Sym_PathFile
25 class Sym_PathFile term where
26 pathfile :: PathFile -> term PathFile
27 default pathfile :: Sym_PathFile (UnT term) => Trans term => PathFile -> term PathFile
28 pathfile = trans . pathfile
30 instance Sym_PathFile Eval where
32 instance Sym_PathFile View where
33 pathfile a = View $ \_p _v -> Text.pack (show a)
34 instance (Sym_PathFile r1, Sym_PathFile r2) => Sym_PathFile (Dup r1 r2) where
35 pathfile x = pathfile x `Dup` pathfile x
36 instance (Sym_PathFile term, Sym_Lambda term) => Sym_PathFile (BetaT term)
38 instance ClassInstancesFor PathFile where
39 proveConstraintFor _ (TyApp _ (TyConst _ _ q) c)
40 | Just HRefl <- proj_ConstKiTy @(K PathFile) @PathFile c
42 _ | Just Refl <- proj_Const @Eq q -> Just Dict
43 | Just Refl <- proj_Const @Show q -> Just Dict
45 proveConstraintFor _c _q = Nothing
46 instance TypeInstancesFor PathFile
48 instance -- Gram_Term_AtomsFor
54 ) => Gram_Term_AtomsFor src ss g PathFile where
58 (\a src -> BinTree0 $ Token_Term $ TermAVT $ (`setSource` src) $ tePathFile a)
62 g_pathfile :: CF g PathFile
67 <*> (concat <$> some ((:) <$> char '/' <*> g_pathfile_section))
68 g_pathfile_section :: CF g FilePath
69 g_pathfile_section = some (choice $ unicat <$> [Unicat_Letter, Unicat_Number])
70 instance (Source src, Inj_Sym ss PathFile) => ModuleFor src ss PathFile where
71 moduleFor = ["PathFile"] `moduleWhere`
75 tyPathFile :: Source src => Inj_Len vs => Type src vs PathFile
76 tyPathFile = tyConst @(K PathFile) @PathFile
78 tePathFile :: Source src => Inj_Sym ss PathFile => PathFile -> Term src ss ts '[] (() #> PathFile)
79 tePathFile a = Term noConstraint tyPathFile $ teSym @PathFile $ pathfile a