Compare commits

..

No commits in common. "c12458a2bf18fc97b96570ff4fee879061526e91" and "4e8e5b9e8432f33dd9dcecba1a9e543ea9cc4173" have entirely different histories.

3 changed files with 27 additions and 25 deletions

View file

@ -6,4 +6,4 @@ main :: IO ()
main = do main = do
text <- getContents text <- getContents
print $ Parsec.parse (File.parse "<stdin>" <* Parsec.eof) "<stdin>" text print $ Parsec.parse (File.parse <* Parsec.eof) "<stdin>" text

View file

@ -1,5 +1,3 @@
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingVia #-}
module Ubc.Parse.Syntax.File module Ubc.Parse.Syntax.File
( File(..) ( File(..)
, parse , parse
@ -19,32 +17,36 @@ import qualified Ubc.Parse.Syntax.Struct as Struct
import qualified Ubc.Parse.Syntax.Function as Function import qualified Ubc.Parse.Syntax.Function as Function
import qualified Ubc.Parse.Syntax.Statement as Statement import qualified Ubc.Parse.Syntax.Statement as Statement
import qualified Ubc.Parse.Syntax.Enumeration as Enumeration import qualified Ubc.Parse.Syntax.Enumeration as Enumeration
import GHC.Generics (Generic, Generically(..))
import Data.Functor ((<&>))
data File = File data File = File
{ name :: String { name :: String
, body :: FileBody , structs :: [Struct]
}
deriving (Show)
data FileBody = FileBody
{ structs :: [Struct]
, functions :: [Function] , functions :: [Function]
, statements :: [Statement] , statements :: [Statement]
, enumerations :: [Enumeration] , enumerations :: [Enumeration]
} }
deriving stock (Show, Generic) deriving (Show)
deriving (Semigroup, Monoid) via Generically FileBody
-- dont use `deriving ... via FileBody` because that leads to a loop, somehow
parse :: Monad m => String -> ParsecT String u m File data FileMember = FileFunction Function
parse source = File source <$!> mconcat <$!> many fileMember | FileStruct Struct
| FileEnumeration Enumeration
| FileStatement Statement
fileMember :: Monad m => ParsecT String u m FileBody accumulateFile :: File -> FileMember -> File
accumulateFile (File name_ sss fs sts es) (FileStruct s) = File name_ (s:sss) fs sts es
accumulateFile (File name_ sss fs sts es) (FileFunction f) = File name_ sss (f:fs) sts es
accumulateFile (File name_ sss fs sts es) (FileStatement s) = File name_ sss fs (s:sts) es
accumulateFile (File name_ sss fs sts es) (FileEnumeration e) = File name_ sss fs sts (e:es)
parse :: Monad m => ParsecT String u m File
parse = foldr (flip accumulateFile) (File "" [] [] [] []) <$!> many fileMember
fileMember :: Monad m => ParsecT String u m FileMember
fileMember = choice fileMember = choice
[ Struct.parse <&> \s -> mempty { structs = [s] } [ FileStruct <$!> Struct.parse
, Function.parse <&> \f -> mempty { functions = [f] } , FileFunction <$!> Function.parse
, Statement.parse <&> \s -> mempty { statements = [s] } , FileStatement <$!> Statement.parse
, Enumeration.parse <&> \e -> mempty { enumerations = [e] } , FileEnumeration <$!> Enumeration.parse
] ]

View file

@ -7,7 +7,7 @@ module Ubc.Parse.Syntax.Struct
where where
-- yay, explicit dependency on ghc -- yay, explicit dependency on ghc
import GHC.Generics (Generic, Generically(..)) import GHC.Generics (Generic)
import Control.Monad ((<$!>)) import Control.Monad ((<$!>))
@ -39,7 +39,7 @@ data StructBody = StructBody
, functions :: [Function] , functions :: [Function]
} }
deriving stock (Generic, Show) deriving stock (Generic, Show)
deriving (Semigroup, Monoid) via Generically StructBody deriving (Semigroup, Monoid) via StructBody
parse :: Monad m => ParsecT String u m Struct parse :: Monad m => ParsecT String u m Struct
parse = do parse = do