Copyright | Copyright 2017 Awake Security |
---|---|
License | Apache-2.0 |
Maintainer | opensource@awakesecurity.com |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Utility types and functions for the rest of language-ninja
.
This module re-exports all of the modules under the Language.Ninja.Misc namespace for convenience.
It is recommended that you import it with the following style:
import qualified Language.Ninja.Misc as Misc
Since: 0.1.0
- data Command
- makeCommand :: Text -> Command
- commandText :: Iso' Command Text
- data Path
- makePath :: Text -> Path
- pathIText :: Iso' Path IText
- pathText :: Iso' Path Text
- pathString :: Iso' Path String
- pathFP :: Iso' Path FilePath
- data IText
- uninternText :: IText -> Text
- internText :: Text -> IText
- itext :: Iso' Text IText
- data Positive
- makePositive :: Int -> Maybe Positive
- fromPositive :: Getter Positive Int
- class Functor ty => Annotated ty where
- annotation :: Annotated ty => Lens' (ty ann) ann
- data Located t
- tokenize :: Maybe Path -> Text -> [Located Text]
- tokenizeFile :: MonadReadFile m => Path -> m [Located Text]
- tokenizeText :: Text -> [Located Text]
- locatedPos :: Lens' (Located t) Position
- locatedVal :: Lens' (Located t) t
- data Spans
- makeSpans :: [Span] -> Spans
- spansSet :: Iso' Spans (HashSet Span)
- data Span
- makeSpan :: Maybe Path -> Offset -> Offset -> Span
- spanPath :: Lens' Span (Maybe Path)
- spanRange :: Lens' Span (Offset, Offset)
- spanStart :: Lens' Span Offset
- spanEnd :: Lens' Span Offset
- data Position
- makePosition :: Maybe Path -> Offset -> Position
- positionFile :: Lens' Position (Maybe Path)
- positionOffset :: Lens' Position Offset
- positionLine :: Lens' Position Line
- positionCol :: Lens' Position Column
- comparePosition :: Position -> Position -> Maybe Ordering
- type Offset = (Line, Column)
- compareOffset :: Offset -> Offset -> Ordering
- offsetLine :: Lens' Offset Line
- offsetColumn :: Lens' Offset Column
- type Line = Int
- type Column = Int
Language.Ninja.Misc.Command
This type represents a POSIX sh
command line.
Since: 0.1.0
Eq Command Source # | |
Ord Command Source # | |
Read Command Source # | |
Show Command Source # | |
Generic Command Source # | |
Hashable Command Source # | |
ToJSON Command Source # | |
FromJSON Command Source # | |
NFData Command Source # | |
(Monad m, Serial m Text) => Serial m Command Source # | Uses the underlying Since: 0.1.0 |
(Monad m, CoSerial m Text) => CoSerial m Command Source # | Uses the underlying Since: 0.1.0 |
type Rep Command Source # | |
Language.Ninja.Misc.Path
This type represents a Unix path string.
Since: 0.1.0
Eq Path Source # | |
Ord Path Source # | |
Read Path Source # | |
Show Path Source # | |
IsString Path Source # | |
Generic Path Source # | |
Hashable Path Source # | |
ToJSON Path Source # | |
ToJSONKey Path Source # | |
FromJSON Path Source # | |
FromJSONKey Path Source # | |
NFData Path Source # | |
(Monad m, Serial m Text) => Serial m Path Source # | Uses the underlying Since: 0.1.0 |
(Monad m, CoSerial m Text) => CoSerial m Path Source # | Uses the underlying Since: 0.1.0 |
type Rep Path Source # | |
pathFP :: Iso' Path FilePath Source #
An isomorphism between a Path
and a FilePath
from system-filepath
.
This uses decodeString
and encodeString
, so all the caveats on
those functions apply here.
Since: 0.1.0
Language.Ninja.Misc.IText
An interned (hash-consed) text type.
This is a newtype over InternedText
from the intern
package.
Since: 0.1.0
Eq IText Source # | |
Ord IText Source # | The Since: 0.1.0 |
Read IText Source # | Inverse of the Since: 0.1.0 |
Show IText Source # | Displays an Since: 0.1.0 |
IsString IText Source # | |
Generic IText Source # | |
Hashable IText Source # | Uses the TODO: perhaps switch to hashing the identifier, since this is likely
pretty hot code given all the Since: 0.1.0 |
ToJSON IText Source # | Converts to JSON string via Since: 0.1.0 |
ToJSONKey IText Source # | Converts to JSON string via Since: 0.1.0 |
FromJSON IText Source # | Inverse of the Since: 0.1.0 |
FromJSONKey IText Source # | Inverse of the Since: 0.1.0 |
NFData IText Source # | Defined by Since: 0.1.0 |
(Monad m, Serial m Text) => Serial m IText Source # | Uses the Since: 0.1.0 |
(Monad m, CoSerial m Text) => CoSerial m IText Source # | Uses the Since: 0.1.0 |
type Rep IText Source # | |
uninternText :: IText -> Text Source #
internText :: Text -> IText Source #
Language.Ninja.Misc.Positive
This type represents a positive number; i.e.: an integer greater than zero.
Since: 0.1.0
Enum Positive Source # | |
Eq Positive Source # | |
Integral Positive Source # | |
Num Positive Source # | This instance uses Since: 0.1.0 |
Ord Positive Source # | |
Read Positive Source # | |
Real Positive Source # | |
Show Positive Source # | |
Generic Positive Source # | |
Hashable Positive Source # | |
ToJSON Positive Source # | |
FromJSON Positive Source # | |
NFData Positive Source # | |
Monad m => Serial m Positive Source # | Uses the underlying Since: 0.1.0 |
Monad m => CoSerial m Positive Source # | Uses the underlying Since: 0.1.0 |
type Rep Positive Source # | |
Language.Ninja.Misc.Annotated
class Functor ty => Annotated ty where Source #
If you have some type that represents an AST node, it is often useful to add a polymorphic "annotation field" to it, which is used for things like source positions.
Specifically, suppose we have the following AST node type:
data Foo = Foo { _fooBar :: !Bar, _fooBaz :: !Baz } deriving (…)
Then an annotation field is added by the following process:
- Add an extra (final) type parameter
ann
to the type. - Add an extra field
_fooAnn :: !ann
. - Derive instances of
Functor
,Foldable
, andTraversable
. - If the type is recursive, add a
Plated
instance. See Language.Ninja.AST.Expr for a complete example of this. - Write an
Annotated
instance with the canonical lens given by the_fooAnn
field. There are plenty of examples around this library.
The end result then looks like:
data Foo ann = Foo { _fooAnn :: !ann , _fooBar :: !Bar , _fooBaz :: !Baz } deriving (…, Functor, Foldable, Traversable) instance Annotated Foo where annotation' = …
Since: 0.1.0
annotation' :: (ann -> ann') -> Lens (ty ann) (ty ann') ann ann' Source #
Given a function that is used when fmap
ing any subterms, return a lens
into the "annotation" field.
When writing an instance, keep in mind that
should
just be the typical definition for a lens into the annotation field.annotation'
id
It should also be true that for any f :: B -> C
and g :: A -> B
,
annotation' (f . g) == annotation' f . annotation' g
Since: 0.1.0
Annotated Expr Source # | The usual definition for Since: 0.1.0 |
Annotated Rule Source # | The usual definition for Since: 0.1.0 |
Annotated Deps Source # | The usual definition for Since: 0.1.0 |
Annotated Build Source # | The usual definition for Since: 0.1.0 |
Annotated Ninja Source # | The usual definition for Since: 0.1.0 |
Annotated LBuild Source # | The usual definition for Since: 0.1.0 |
Annotated LName Source # | The usual definition for Since: 0.1.0 |
Annotated Lexeme Source # | The usual definition for Since: 0.1.0 |
annotation :: Annotated ty => Lens' (ty ann) ann Source #
This is just shorthand for
.annotation'
id
Since: 0.1.0
Language.Ninja.Misc.Located
This datatype represents a value annotated with a source location.
Since: 0.1.0
Functor Located Source # | |
Foldable Located Source # | |
Traversable Located Source # | |
(Monad m, Serial m Text, Serial m t) => Serial m (Located t) Source # | Default Since: 0.1.0 |
(Monad m, CoSerial m Text, CoSerial m t) => CoSerial m (Located t) Source # | Default Since: 0.1.0 |
Eq t => Eq (Located t) Source # | |
Show t => Show (Located t) Source # | |
Generic (Located t) Source # | |
Hashable t => Hashable (Located t) Source # | Default Since: 0.1.0 |
ToJSON t => ToJSON (Located t) Source # | Converts to Since: 0.1.0 |
FromJSON t => FromJSON (Located t) Source # | Inverse of the Since: 0.1.0 |
NFData t => NFData (Located t) Source # | Default Since: 0.1.0 |
type Rep (Located t) Source # | |
tokenizeFile :: MonadReadFile m => Path -> m [Located Text] Source #
tokenizeText :: Text -> [Located Text] Source #
This function is equivalent to tokenize Nothing
.
Since: 0.1.0
locatedVal :: Lens' (Located t) t Source #
The value underlying this located value.
Since: 0.1.0
A type representing a set of source spans.
Since: 0.1.0
Eq Spans Source # | |
Show Spans Source # | |
Generic Spans Source # | |
Semigroup Spans Source # | |
Monoid Spans Source # | |
Hashable Spans Source # | |
ToJSON Spans Source # | |
FromJSON Spans Source # | |
NFData Spans Source # | |
(Monad m, Serial m (HashSet Span)) => Serial m Spans Source # | Default Since: 0.1.0 |
(Monad m, CoSerial m (HashSet Span)) => CoSerial m Spans Source # | Default Since: 0.1.0 |
type Rep Spans Source # | |
Represents a span of source code.
Since: 0.1.0
Eq Span Source # | |
Show Span Source # | |
Generic Span Source # | |
Hashable Span Source # | Default Since: 0.1.0 |
ToJSON Span Source # | Converts to Since: 0.1.0 |
FromJSON Span Source # | Inverse of the Since: 0.1.0 |
NFData Span Source # | Default Since: 0.1.0 |
(Monad m, Serial m Text) => Serial m Span Source # | Default Since: 0.1.0 |
(Monad m, CoSerial m Text) => CoSerial m Span Source # | Default Since: 0.1.0 |
type Rep Span Source # | |
:: Maybe Path | The file in which this span resides, if any. |
-> Offset | The start offset. |
-> Offset | The end offset. |
-> Span |
Construct a Span
from a given start position to a given end position.
Since: 0.1.0
spanPath :: Lens' Span (Maybe Path) Source #
A lens into the (nullable) path associated with a Span
.
Since: 0.1.0
This datatype represents the position of a cursor in a text file.
Since: 0.1.0
Eq Position Source # | |
Show Position Source # | |
Generic Position Source # | |
Hashable Position Source # | Default Since: 0.1.0 |
ToJSON Position Source # | Converts to Since: 0.1.0 |
FromJSON Position Source # | Inverse of the Since: 0.1.0 |
NFData Position Source # | Default Since: 0.1.0 |
(Monad m, Serial m Text) => Serial m Position Source # | Default Since: 0.1.0 |
(Monad m, CoSerial m Text) => CoSerial m Position Source # | Default Since: 0.1.0 |
type Rep Position Source # | |
makePosition :: Maybe Path -> Offset -> Position Source #
Construct a Position
from a (nullable) path and a (line, column)
pair.
Since: 0.1.0
positionFile :: Lens' Position (Maybe Path) Source #
The path of the file pointed to by this position, if any.
Since: 0.1.0
positionOffset :: Lens' Position Offset Source #
The offset in the file pointed to by this position.
Since: 0.1.0
positionLine :: Lens' Position Line Source #
The line number in the file pointed to by this position.
Since: 0.1.0
positionCol :: Lens' Position Column Source #
The column number in the line pointed to by this position.
Since: 0.1.0
offsetColumn :: Lens' Offset Column Source #
A lens into the Line
associated with an Offset
.
Read the description of offsetLine
for an understanding of why this
exists and why you should use it instead of _2
.
Since: 0.1.0