{-| Module : Prosidy.Compile Description : Compile Prosidy documents into other shapes Copyright : ©2020 James Alexander Feldman-Crough License : MPL-2.0 Maintainer : alex@fldcr.com -} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE ApplicativeDo #-} {-# LANGUAGE DerivingVia #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} module Prosidy.Compile ( -- * Accessors escapeHatch , getContent , matchContent , optParse , prop , reqParse , traversing , self -- * Reëxports , RuleT , Rule , CanMatch , Error(..) , ErrorSet , module Prosidy.Compile.Match , module Prosidy.Compile.Run ) where import Prelude hiding ( break ) import Prosidy.Compile.Core import Prosidy.Compile.Error import Prosidy.Compile.Match import Prosidy.Compile.Run import Data.Text ( Text ) import qualified Prosidy as P ------------------------------------------------------------------------------- -- | Access the inner 'Prosidy.Types.Content' of a node. getContent :: P.HasContent i => RuleT (P.Content i) e f a -> RuleT i e f a getContent = rule . GetContent -- | Traverse over each item in a node's 'P.Content' via fallible matches. matchContent :: (Traversable t, P.HasContent i, t x ~ P.Content i, CanMatch x) => Match x e f a -> RuleT i e f (t a) matchContent = getContent . traversing . match -- | Parse an optional setting from a node with attached 'P.Metadata'. optParse :: P.HasMetadata i => P.Key -> (Text -> Either String a) -> RuleT i e f (Maybe a) optParse key = rule . GetSetting id key -- | Check if a property is set on a node with attached 'P.Metadata'. prop :: P.HasMetadata i => P.Key -> RuleT i e f Bool prop = rule . GetProperty id -- | Parse an required setting from a node with attached 'P.Metadata'. reqParse :: P.HasMetadata i => P.Key -> (Text -> Either String a) -> RuleT i e f a reqParse key = rule . GetRequiredSetting key -- | Lift a 'RuleT' so that it operates on a traversable structure. traversing :: Traversable t => RuleT i e f a -> RuleT (t i) e f (t a) traversing = rule . Traverse id id -- | Access the contents of a node. self :: RuleT i e f i self = rule $ GetSelf id -- | Do anything you want with a node. This should be used sparingly! The -- actions you perform inside of this function are invisible to inspection. escapeHatch :: (i -> f (Either (Error e) a)) -> RuleT i e f a escapeHatch = rule . Lift