Safe Haskell | None |
---|---|
Language | GHC2021 |
GTVM.Studio
Synopsis
- newtype ScpId = ScpId {}
- type TLSeg' = TLSeg (Const () :: Type -> Type) Text
- data Studio (m :: k) a where
- WriteTl :: forall {k} (m :: k). TLSeg' -> Studio m ()
- ReadTl :: forall {k} (m :: k). Studio m (Maybe TLSeg')
- JumpTlInit :: forall {k} (m :: k). Studio m ()
- NextTl :: forall {k} (m :: k). Studio m ()
- PrevTl :: forall {k} (m :: k). Studio m ()
- LoadScp :: forall {k} (m :: k). ScpId -> Studio m ()
- GenerateFreshScpTl :: forall {k} (m :: k). Path Rel Dir -> Studio m ()
- LoadScpTl :: forall {k} (m :: k). Path Rel Dir -> Studio m ()
- SaveScpTl :: forall {k} (m :: k). Path Rel Dir -> Studio m ()
- writeTl :: forall (r :: EffectRow). Member (Studio :: (Type -> Type) -> Type -> Type) r => TLSeg' -> Sem r ()
- readTl :: forall (r :: EffectRow). Member (Studio :: (Type -> Type) -> Type -> Type) r => Sem r (Maybe TLSeg')
- jumpTlInit :: forall (r :: EffectRow). Member (Studio :: (Type -> Type) -> Type -> Type) r => Sem r ()
- nextTl :: forall (r :: EffectRow). Member (Studio :: (Type -> Type) -> Type -> Type) r => Sem r ()
- prevTl :: forall (r :: EffectRow). Member (Studio :: (Type -> Type) -> Type -> Type) r => Sem r ()
- loadScp :: forall (r :: EffectRow). Member (Studio :: (Type -> Type) -> Type -> Type) r => ScpId -> Sem r ()
- generateFreshScpTl :: forall (r :: EffectRow). Member (Studio :: (Type -> Type) -> Type -> Type) r => Path Rel Dir -> Sem r ()
- loadScpTl :: forall (r :: EffectRow). Member (Studio :: (Type -> Type) -> Type -> Type) r => Path Rel Dir -> Sem r ()
- saveScpTl :: forall (r :: EffectRow). Member (Studio :: (Type -> Type) -> Type -> Type) r => Path Rel Dir -> Sem r ()
- jumpTl :: forall (r :: EffectRow). Members '[Studio :: (Type -> Type) -> Type -> Type] r => Natural -> Sem r ()
- loadFreshScpTl :: forall (r :: EffectRow). Members '[Studio :: (Type -> Type) -> Type -> Type] r => Path Rel Dir -> Sem r ()
- data St = St {}
- setAt :: Int -> a -> [a] -> [a]
- runStudio :: forall (r :: EffectRow) a. Members '[State St :: (Type -> Type) -> Type -> Type, Output Text :: (Type -> Type) -> Type -> Type, Embed IO] r => Path Abs Dir -> Sem ((Studio :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a
- studioYamlRes :: MonadThrow m => FilePath -> Text -> m (Path Rel File)
- scpPrevTlIdx :: forall (f :: Strength) a. SCP f a -> Int -> Maybe Int
- scpNextTlIdx :: forall (f :: Strength) a. SCP f a -> Int -> Either Int Int
- tlSegIsEmpty :: forall a (f :: Type -> Type). (Eq a, Monoid a) => TLSeg f a -> Bool
- studioLog :: forall (r :: EffectRow). Member (Output Text :: (Type -> Type) -> Type -> Type) r => Text -> Sem r ()
- genEmptyScptl :: SCP 'Weak Text -> [TLSeg']
- rLoadAndGenFirstScript :: IO ()
- runStudioLog :: forall (r :: EffectRow) o a. Member (Embed IO) r => (o -> IO ()) -> Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a
- pLoadAndGenFirstScript :: forall (r :: EffectRow). Members '[Studio :: (Type -> Type) -> Type -> Type, Embed IO] r => Sem r ()
- tlsegTextbox :: a -> TLSeg (Const () :: Type -> Type) a
Documentation
type TLSeg' = TLSeg (Const () :: Type -> Type) Text Source #
Yes, we're ignoring the source fields. We'll fill them in during an export pass. Easier on the brain.
data Studio (m :: k) a where Source #
Constructors
WriteTl :: forall {k} (m :: k). TLSeg' -> Studio m () | |
ReadTl | |
JumpTlInit | |
Fields
| |
NextTl | |
Fields
| |
PrevTl | |
Fields
| |
LoadScp | |
GenerateFreshScpTl | |
LoadScpTl | |
SaveScpTl | |
writeTl :: forall (r :: EffectRow). Member (Studio :: (Type -> Type) -> Type -> Type) r => TLSeg' -> Sem r () Source #
readTl :: forall (r :: EffectRow). Member (Studio :: (Type -> Type) -> Type -> Type) r => Sem r (Maybe TLSeg') Source #
jumpTlInit :: forall (r :: EffectRow). Member (Studio :: (Type -> Type) -> Type -> Type) r => Sem r () Source #
nextTl :: forall (r :: EffectRow). Member (Studio :: (Type -> Type) -> Type -> Type) r => Sem r () Source #
prevTl :: forall (r :: EffectRow). Member (Studio :: (Type -> Type) -> Type -> Type) r => Sem r () Source #
loadScp :: forall (r :: EffectRow). Member (Studio :: (Type -> Type) -> Type -> Type) r => ScpId -> Sem r () Source #
generateFreshScpTl :: forall (r :: EffectRow). Member (Studio :: (Type -> Type) -> Type -> Type) r => Path Rel Dir -> Sem r () Source #
loadScpTl :: forall (r :: EffectRow). Member (Studio :: (Type -> Type) -> Type -> Type) r => Path Rel Dir -> Sem r () Source #
saveScpTl :: forall (r :: EffectRow). Member (Studio :: (Type -> Type) -> Type -> Type) r => Path Rel Dir -> Sem r () Source #
jumpTl :: forall (r :: EffectRow). Members '[Studio :: (Type -> Type) -> Type -> Type] r => Natural -> Sem r () Source #
Resets and steps to the translation target SCP command with the requested index.
TODO better behaviour if we jump too far (don't keep spamming nextTl
)? but
this should be prefaced with a UI check that the index exists
loadFreshScpTl :: forall (r :: EffectRow). Members '[Studio :: (Type -> Type) -> Type -> Type] r => Path Rel Dir -> Sem r () Source #
Generate a fresh SCPTL for the currently loaded SCP, place in the requested studio folder and load immediately.
Constructors
St | |
Instances
runStudio :: forall (r :: EffectRow) a. Members '[State St :: (Type -> Type) -> Type -> Type, Output Text :: (Type -> Type) -> Type -> Type, Embed IO] r => Path Abs Dir -> Sem ((Studio :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a Source #
studioYamlRes :: MonadThrow m => FilePath -> Text -> m (Path Rel File) Source #
studioLog :: forall (r :: EffectRow). Member (Output Text :: (Type -> Type) -> Type -> Type) r => Text -> Sem r () Source #
Required to avoid lots of type annotation, that's life Jim
rLoadAndGenFirstScript :: IO () Source #
runStudioLog :: forall (r :: EffectRow) o a. Member (Embed IO) r => (o -> IO ()) -> Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a Source #