Outline Magic and Faith systems

develop
Rin 2024-02-08 19:52:49 +11:00
parent 34d0dcbf03
commit b8e495c064
6 changed files with 87 additions and 16 deletions

View File

@ -4,3 +4,8 @@
[1121/233648.610:ERROR:registration_protocol_win.cc(107)] CreateFile: The system cannot find the file specified. (0x2)
[1121/233649.357:ERROR:registration_protocol_win.cc(107)] CreateFile: The system cannot find the file specified. (0x2)
[1121/233650.157:ERROR:registration_protocol_win.cc(107)] CreateFile: The system cannot find the file specified. (0x2)
[0131/173153.371:ERROR:registration_protocol_win.cc(107)] CreateFile: The system cannot find the file specified. (0x2)
[0202/232742.118:ERROR:registration_protocol_win.cc(107)] CreateFile: The system cannot find the file specified. (0x2)
[0202/232742.577:ERROR:registration_protocol_win.cc(107)] CreateFile: The system cannot find the file specified. (0x2)
[0202/232742.986:ERROR:registration_protocol_win.cc(107)] CreateFile: The system cannot find the file specified. (0x2)
[0202/232743.401:ERROR:registration_protocol_win.cc(107)] CreateFile: The system cannot find the file specified. (0x2)

View File

@ -23,8 +23,10 @@ source-repository head
library
exposed-modules:
Aspect
Faith
Item
Lib
Magic
Material
Overseer
Structure

View File

@ -6,19 +6,3 @@ import Text.ParserCombinators.Parsec
-- They are nominally formed of an Aspect type (which amounts to an Enum), as well an amount.
|--}
-- TODO: Figure out how to structure this... Type level counting????
data Aspect Type where
GenericAspect :: {
aspect :: AspectI,
amount :: Int
} -> Aspect a
parseAspect :: Parser AspectI
parseAspect = do
a <- many char
return $ case a of
"Flam" -> Flammable
"Cond" -> Conductive
"Cool" -> Cooling

12
src/Faith.hs Normal file
View File

@ -0,0 +1,12 @@
module Faith where
{--| The Faith system uses a system of stringing together prayers to create effects. Miracles differ from magic in that
-- a prayer can be ended at any time, and deployed at a moment's notice. This allows for dynamic adjustment of effects
-- if the caster's situation changes. On the flip side, the prayers may require somatic or verbal components or other
-- active costs during execution.
-- Prayers themselves have slightly randomised effects per playthrough, while keeping to a theme.
-- In the future, prayer usage should be tracked on a server to provide dynamic resonance and dissonance effects.
|--}

View File

@ -9,3 +9,5 @@ class It where
volume :: Volume Integer
mass :: Mass Integer
class It => We where
damage :: [(Aspect, Int)]

66
src/Magic.hs Normal file
View File

@ -0,0 +1,66 @@
{-# LANGUAGE NoImplicitPrelude #-}
module Magic where
import Numeric.Units.Dimensional.Prelude
import Data.String (String)
import Data.Kind (Type)
{--| The intent of the magic system is to allow for the creation of complex effects in the style of a programming language,
-- couched in the language of fantasy writing. A lot of the semantics will match Haskell for both learning and pragmatic reasons.
--
-- In this system, spells are built from individual effect blocks. Effect chains have an execution time. Once triggered, they
-- take mindspace while compiling, and are ready to be released once finished. Retaining a spell once its ready requires feats
-- and yet more mindspace.
-- On the bright side, once compilation is triggered, no further active action is required from the caster.
|--}
-- class Noun where
-- overlays :: [String] -- TODO: Replace this with proper Aspects once they're done
-- class Verb v where
-- data ActionTypes :: Type -> Type
-- effects :: ActionTypes n
-- instance Verb Create where
-- data ActionTypes = n -> n
-- -- TODO: How to structrue Verbs and Nouns so that they actually form restrictions
-- -- It may not be practical to do this at the type-level.
data Noun where
Noun :: {
canonicalName :: String,
description :: String
} -> Noun
data Verb n where
RawVerb :: {
canonicalName :: String,
description :: String
} -> Verb
AppliedVerb :: (n ~ Noun) => {
appliedName :: String,
description :: String
} -> Verb n
data Target t where
Target :: {
canonicalName :: String,
description :: String
} -> Target t
data Guideline v n t where
Guideline :: (v ~ Verb, n ~ Noun, t ~ Target) => {
level :: Int,
action :: t -> t,
description :: String
} -> Guideline v n t
data EffectBlock t where
SimpleEffect :: {
effect :: MagicGuideline Noun Verb
} -> EffectBlock t