code
stringlengths 2
1.05M
| repo_name
stringlengths 5
101
| path
stringlengths 4
991
| language
stringclasses 3
values | license
stringclasses 5
values | size
int64 2
1.05M
|
---|---|---|---|---|---|
{-# LANGUAGE OverloadedStrings #-}
module Network.XMPP.Auth where
import Network.XMPP.XMLParse
import Network.XMPP.XMPPMonad
import Network.XMPP.Stanzas
import Data.Text (Text)
-- |Non-SASL authentication, following XEP-0078.
startAuth :: Text -- ^Username (part before \@ in JID)
-> Text -- ^Server (part after \@ in JID)
-> Text -- ^Password
-> Text -- ^Resource (unique identifier for this connection)
-> XMPP Integer -- ^Error number. Zero if authentication succeeded.
startAuth username server password resource = do
response <- sendIqWait server "get" [XML "query"
[("xmlns","jabber:iq:auth")]
[XML "username"
[]
[CData username]]]
case xmlPath ["query","password"] response of
Nothing -> return 1 -- plaintext authentication not supported by server
-- http://xmpp.org/extensions/attic/jep-0078-1.7.html
-- "If there is no such username, the server SHOULD NOT return an error"
-- So server can return error here, if username is wrong.
Just _ -> do
response' <- sendIqWait server "set" [XML "query"
[("xmlns","jabber:iq:auth")]
[XML "username" []
[CData username],
XML "password" []
[CData password],
XML "resource" []
[CData resource]]]
return $ getErrorCode response'
| drpowell/XMPP | Network/XMPP/Auth.hs | Haskell | bsd-3-clause | 1,862 |
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Language.JavaScript.SpiderMonkey.Parser where
import Data.Aeson
import Data.Aeson.Types
import Data.Aeson.TH
import Data.Int
import Control.Applicative
import Data.Monoid()
import Control.Monad
import Data.String
import Data.Text hiding (filter)
import Control.Monad.Reader
import Data.Scientific (Scientific)
import qualified Data.Map.Strict as Map
import Prelude hiding (either)
-- low level types
data SourceLocation = SourceLocation {source :: Maybe String
,start :: Position
,end :: Position}
| NoLocation
deriving (Eq, Show)
instance FromJSON SourceLocation where
parseJSON (Object o) = SourceLocation <$>
o .: "source" <*>
o .: "start" <*>
o .: "end"
parseJSON Null = pure NoLocation
data Position = Position {line :: Int32
,column :: Int32
}
deriving (Eq, Show)
$(deriveJSON defaultOptions ''Position)
data Node a = Node {nodeType :: String
,nodeBuilder :: Builder a}
instance Functor Node where
fmap f node' = node' {nodeBuilder = f <$> nodeBuilder node'}
instance Applicative Node where
pure x = Node {nodeType = "", nodeBuilder = pure x}
ndf <*> ndx = let f = nodeBuilder ndf
ty= nodeType ndf
x = nodeBuilder ndx
in Node ty (f <*> x)
cases :: [Node a] -> (Value -> Parser a)
cases nds = \v -> case v of
Object o -> do type_ <- getType o
case matchType type_ nds of
Just node' -> runBuilder (nodeBuilder node') o
Nothing -> fail $ "Unexpected node type: " ++ (show type_) ++ " options were: " ++ (Data.String.unwords $ Prelude.map nodeType nds)
_ -> typeMismatch "Node" v
node :: String -> (SourceLocation -> f) -> Node f
node name ctor = Node name $ ctor <$> getLocation
liftJSON :: (FromJSON a) => Node a
liftJSON = Node {nodeType = ""
,nodeBuilder = do o <- ask
lift $ parseJSON $ Object o}
type Builder a = ReaderT Object Parser a
runBuilder :: Builder a -> Object -> Parser a
runBuilder = runReaderT
field :: FromJSON a => Text -> Node a
field name = Node {nodeType = ""
,nodeBuilder = do o <- ask
lift (o .: name)}
instance FromJSON a => IsString (Node a) where
fromString s = field (fromString s)
matchType :: String -> [Node a] -> Maybe (Node a)
matchType type_ = safeHead . filter (\n -> type_ == nodeType n)
where safeHead [] = Nothing
safeHead (x:_) = Just x
getType :: Object -> Parser String
getType o = o .: "type"
getLocation :: Builder SourceLocation
getLocation = ask >>= \o -> lift (o .: "loc")
data Program = Program { loc :: SourceLocation, body :: [Statement] }
deriving (Eq, Show)
instance FromJSON Program where
parseJSON (Object o') = p' o'
where p' o = Program <$>
o .: "loc" <*>
o .: "body" --cases [node "Program" Program <*> "body"]
parseJSON _ = mzero
data Function = Function {funcId :: Maybe Identifier
,funcParams :: [Pattern]
,funcDefaults :: [Expression]
,funcRest :: Maybe Identifier
-- spidermonkey supports closure expressions, which means body could theoretically also be an Expression
-- We don't support it because it isn't standard in ES5.
-- See: https://developer.mozilla.org/en-US/docs/Mozilla/Projects/SpiderMonkey/Parser_API#Functions
,funcBody :: Statement
,funcGenerator :: Bool}
deriving (Eq, Show)
instance FromJSON Function where
parseJSON (Object o) = Function <$>
o .: "id" <*>
o .: "params" <*>
o .: "defaults" <*>
o .: "rest" <*>
o .: "body" <*>
o .: "generator"
parseJSON _ = mzero
-- | The Aeson instance for Either is pretty inuntuitive and
-- unimaginative, so we need to circumvent that
either :: forall a b. (FromJSON a, FromJSON b) => Text -> Node (Either a b)
either name = Node {nodeType = ""
,nodeBuilder = do o <- ask
lift ((Left <$> (o .: name :: Parser a)) <|>
(Right <$> (o .: name :: Parser b)))
}
data Statement = EmptyStatement SourceLocation
| BlockStatement SourceLocation [Statement]
| ExpressionStatement SourceLocation Expression
| IfStatement SourceLocation Expression Statement (Maybe Statement)
| LabeledStatement SourceLocation Identifier Statement
| BreakStatement SourceLocation (Maybe Identifier)
| ContinueStatement SourceLocation (Maybe Identifier)
| WithStatement SourceLocation Expression Statement
| SwitchStatement SourceLocation Expression [SwitchCase] Bool
| ReturnStatement SourceLocation (Maybe Expression)
| ThrowStatement SourceLocation Expression
| TryStatement SourceLocation Statement (Maybe CatchClause) [CatchClause] (Maybe Statement)
| WhileStatement SourceLocation Expression Statement
| DoWhileStatement SourceLocation Statement Expression
| ForStatement SourceLocation ForInit (Maybe Expression) (Maybe Expression) Statement
| ForInStatement SourceLocation (Either VariableDeclaration Expression) Expression Statement Bool
| ForOfStatement SourceLocation (Either VariableDeclarator Expression) Expression Statement
| LetStatement SourceLocation [VariableDeclarator] Statement
| DebuggerStatement SourceLocation
| FunctionDeclarationStatement SourceLocation Function
| VariableDeclarationStatement SourceLocation VariableDeclaration
deriving (Eq, Show)
instance FromJSON Statement where
parseJSON = parse'
where parse' =
cases
[node "EmptyStatement" EmptyStatement
,node "BlockStatement" BlockStatement <*> "body"
,node "ExpressionStatement" ExpressionStatement <*> "expression"
,node "IfStatement" IfStatement <*> "test" <*> "consequent" <*> "alternate"
,node "LabeledStatement" LabeledStatement <*> "label" <*> "body"
,node "BreakStatement" BreakStatement <*> "label"
,node "ContinueStatement" ContinueStatement <*> "label"
,node "WithStatement" WithStatement <*> "object" <*> "body"
,node "SwitchStatement" SwitchStatement <*> "discriminant" <*> "cases" <*> "lexical"
,node "ReturnStatement" ReturnStatement <*> "argument"
,node "ThrowStatement" ThrowStatement <*> "argument"
,node "TryStatement" TryStatement <*> "block" <*> "handler" <*> "guardedHandlers" <*> "finalizer"
,node "WhileStatement" WhileStatement <*> "test" <*> "body"
,node "DoWhileStatement" DoWhileStatement <*> "body" <*> "test"
,node "ForStatement" ForStatement <*> "init" <*> "test" <*> "update" <*> "body"
,node "ForInStatement" ForInStatement <*> either "left" <*> "right" <*> "body" <*> "each"
,node "ForOfStatement" ForOfStatement <*> either "left" <*> "right" <*> "body"
,node "LetStatement" LetStatement <*> "head" <*> "body"
,node "DebuggerStatement" DebuggerStatement
,node "FunctionDeclaration" FunctionDeclarationStatement <*> liftJSON
,node "VariableDeclaration" VariableDeclarationStatement <*> liftJSON
]
data ForInit = VarInit VariableDeclaration
| ExprInit Expression
| NoInit
deriving (Eq, Show)
instance FromJSON ForInit where
parseJSON v = case v of
(Object _)-> (VarInit <$> (parseJSON v :: Parser VariableDeclaration))
<|> (ExprInit <$> (parseJSON v :: Parser Expression))
Null -> return $ NoInit
data VariableDeclaration = VariableDeclaration SourceLocation [VariableDeclarator] DeclarationKind
deriving (Eq, Show)
instance FromJSON VariableDeclaration where
parseJSON = cases [node "VariableDeclaration" VariableDeclaration <*>
"declarations" <*> "kind"]
data VariableDeclarator = VariableDeclarator SourceLocation Pattern (Maybe Expression)
deriving (Eq, Show)
instance FromJSON VariableDeclarator where
parseJSON = cases [node "VariableDeclarator" VariableDeclarator <*> "id" <*> "init"]
data DeclarationKind = DVar | DLet | DConst
deriving (Eq, Show)
instance FromJSON DeclarationKind where
parseJSON (String t) = pure $ case t of
"var" -> DVar
"let" -> DLet
"const" -> DConst
parseJSON _ = mzero
data Expression = ThisExpression SourceLocation
| ArrayExpression SourceLocation [Maybe Expression]
| ObjectExpression SourceLocation [Property]
| FunctionExpression SourceLocation Function
| ArrowExpression SourceLocation Function
| SequenceExpression SourceLocation [Expression]
| UnaryExpression SourceLocation UnaryOperator Bool Expression
| BinaryExpression SourceLocation BinaryOperator Expression Expression
| AssignmentExpression SourceLocation AssignmentOperator Expression Expression
| UpdateExpression SourceLocation UpdateOperator Expression Bool
| LogicalExpression SourceLocation LogicalOperator Expression Expression
| ConditionalExpression SourceLocation Expression Expression Expression
| NewExpression SourceLocation Expression [Expression]
| CallExpression SourceLocation Expression [Expression]
| MemberExpression SourceLocation Expression (Either Identifier Expression) Bool
-- The following expression types are spidermonkey-specific, so althought it would be nice to parse
-- them, they are not supposed to show up in valid ecma262 syntax.
-- | YieldExpression SourceLocation (Maybe Expression)
-- | ComprehensionExpression SourceLocation Expression [ComprehensionBlock] (Maybe Expression)
-- | GeneratorExpression SourceLocation Expression [ComprehensionBlock] (Maybe Expression)
-- | GraphExpression SourceLocation Word32 Literal
-- | LetExpression SourceLocation [VariableDeclarator] Expression
| LiteralExpression SourceLocation Literal
| IdentifierExpression SourceLocation Identifier
deriving (Eq, Show)
instance FromJSON Expression where
parseJSON =
cases
[node "ThisExpression" ThisExpression
,node "ArrayExpression" ArrayExpression <*> "elements"
,node "ObjectExpression" ObjectExpression <*> "properties"
,node "FunctionExpression" FunctionExpression <*> liftJSON
,node "ArrowExpression" ArrowExpression <*> liftJSON
,node "SequenceExpression" SequenceExpression <*> "expressions"
,node "UnaryExpression" UnaryExpression <*> "operator" <*> "prefix" <*> "argument"
,node "BinaryExpression" BinaryExpression <*> "operator" <*> "left" <*> "right"
,node "AssignmentExpression" AssignmentExpression <*> "operator" <*> "left" <*> "right"
,node "UpdateExpression" UpdateExpression <*> "operator" <*> "argument" <*> "prefix"
,node "LogicalExpression" LogicalExpression <*> "operator" <*> "left" <*> "right"
,node "ConditionalExpression" ConditionalExpression <*> "test" <*> "consequent" <*> "alternate"
,node "NewExpression" NewExpression <*> "callee" <*> "arguments"
,node "CallExpression" CallExpression <*> "callee" <*> "arguments"
,node "MemberExpression" MemberExpression <*> "object" <*> either "property" <*> "computed"
,node "Literal" LiteralExpression <*> liftJSON
,node "Identifier" IdentifierExpression <*> liftJSON
]
data Property = Property SourceLocation (Either Literal Identifier) Expression PropertyKind
deriving (Eq, Show)
instance FromJSON Property where
parseJSON = cases [node "Property" Property <*> either "key" <*> "value" <*> "kind"]
data PropertyKind = PInit | PGet | PSet
deriving (Eq, Show)
instance FromJSON PropertyKind where
parseJSON (String t) = pure $ case t of
"init" -> PInit
"get" -> PGet
"set" -> PSet
parseJSON _ = mzero
data Pattern = ObjectPattern SourceLocation [PatternProperty]
| ArrayPattern SourceLocation [Maybe Pattern]
| IdentifierPattern SourceLocation Identifier
deriving (Eq, Show)
instance FromJSON Pattern where
parseJSON = cases
[node "ObjectPattern" ObjectPattern <*> "properties"
,node "ArrayPattern" ArrayPattern <*> "elements"
,node "Identifier" IdentifierPattern <*> liftJSON
]
data PatternProperty = PatternProperty (Either Literal Identifier) Pattern
deriving (Eq, Show)
instance FromJSON PatternProperty where
parseJSON (Object o) = PatternProperty <$>
((Left <$> (o .: "key" :: Parser Literal)) <|>
(Right <$> (o .: "key" :: Parser Identifier))) <*>
o .: "value"
parseJSON _ = mzero
data SwitchCase = SwitchCase SourceLocation (Maybe Expression) [Statement]
deriving (Eq, Show)
instance FromJSON SwitchCase where
parseJSON = cases [node "SwitchCase" SwitchCase <*> "test" <*> "consequent"]
data CatchClause = CatchClause SourceLocation Pattern (Maybe Expression) Statement
deriving (Eq, Show)
instance FromJSON CatchClause where
parseJSON = cases [node "CatchClause" CatchClause <*> "param" <*> "guard" <*> "body"]
data ComprehensionBlock = ComprehensionBlock SourceLocation Pattern Expression Bool
deriving (Eq, Show)
instance FromJSON ComprehensionBlock where
parseJSON = cases [node "ComprehensionBlock" ComprehensionBlock <*> "left" <*> "right" <*> "each"]
data Identifier = Identifier SourceLocation Text
deriving (Eq, Show)
instance FromJSON Identifier where
parseJSON = cases [node "Identifier" Identifier <*> "name"]
data Literal = LString SourceLocation Text
| LBool SourceLocation Bool
| LNull SourceLocation
| LNumber SourceLocation Scientific
-- | RegExp SourceLocation String
deriving (Eq, Show)
instance FromJSON Literal where
parseJSON (Object o) = do ty <- getType o
unless (ty == "Literal") mzero
loc' <- o .: "loc"
v <- o .: "value"
return $ case v of
String s -> LString loc' s
Bool b -> LBool loc' b
Null -> LNull loc'
Number n -> LNumber loc' n
parseJSON _ = mzero
enum :: [(Text, a)] -> Value -> Parser a
enum m = let mp = Map.fromList m
in \v -> case v of
String t -> case Map.lookup t mp of
Just a -> return a
Nothing -> mzero
_ -> mzero
data UnaryOperator = (:.-:) | (:.+:) | (:!:) | (:~:) | Typeof | Void | Delete
deriving (Eq, Show)
instance FromJSON UnaryOperator where
parseJSON = enum [("-", (:.-:)), ("+", (:.+:)), ("!", (:!:)), ("~", (:~:)), ("typeof", Typeof), ("void", Void), ("delete", Delete)]
data BinaryOperator = (:==:) | (:!=:) | (:===:) | (:!==:)
| (:<:) | (:<=:) | (:>:) | (:>=:) | (:<<:) | (:>>:)
| (:>>>:) | (:+:) | (:-:) | (:*:) | (:/:)
| (:%:) | (:|:) | (:^:) | (:&:) | In | Instanceof | (:..:)
deriving (Eq, Show)
instance FromJSON BinaryOperator where
parseJSON = enum [("==", (:==:)), ("!=", (:!=:)), ("===", (:===:)), ("!==", (:!==:)), ("<", (:<:)), ("<=", (:<=:)), (">", (:>:)), (">=", (:>=:)), ("<<", (:<<:)), (">>", (:>>:)), (">>>", (:>>>:)), ("+", (:+:)), ("-", (:-:)), ("*", (:*:)), ("/", (:/:)), ("%", (:%:)), ("|", (:|:)), ("^", (:^:)), ("&", (:&:)), ("in", In), ("instanceof", Instanceof), ("..", (:..:))]
data LogicalOperator = (:||:) | (:&&:)
deriving (Eq, Show)
instance FromJSON LogicalOperator where
parseJSON = enum [("||", (:||:)), ("&&", (:&&:))]
data AssignmentOperator = (:=:) | (:+=:) | (:-=:) | (:*=:) | (:/=:) | (:%=:)
| (:<<=:) | (:>>=:) | (:>>>=:) | (:|=:) | (:^=:) | (:&=:)
deriving (Eq, Show)
instance FromJSON AssignmentOperator where
parseJSON = enum [("=", (:=:)), ("+=", (:+=:)), ("-=", (:-=:)), ("*=", (:*=:)), ("/=", (:/=:)), ("%=", (:%=:)), ("<<=", (:<<=:)), (">>=", (:>>=:)), (">>>=", (:>>>=:)), ("|=", (:|=:)), ("^=", (:^=:)), ("&=", (:&=:))]
data UpdateOperator = (:++:) | (:--:)
deriving (Eq, Show)
instance FromJSON UpdateOperator where
parseJSON = enum [("++", (:++:)), ("--", (:--:))]
| jswebtools/mozilla-js-parser-api | src/Language/JavaScript/SpiderMonkey/Parser.hs | Haskell | bsd-3-clause | 17,968 |
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# OPTIONS_GHC -fno-warn-deprecations #-}
module Test.Pos.Util.Tripping where
import qualified Prelude
import Universum
import Data.Aeson (FromJSON, ToJSON, eitherDecode, encode)
import Data.Text.Internal.Builder (fromText, toLazyText)
import qualified Data.Yaml as Y
import Formatting.Buildable (Buildable (..))
import Hedgehog (Gen, Group, MonadTest, discoverPrefix, success,
tripping)
import Hedgehog.Internal.Property (Diff (..), Property, TestLimit,
annotate, failWith, forAllWith, property, withTests)
import Hedgehog.Internal.Show (showPretty, valueDiff)
import Hedgehog.Internal.TH (TExpQ)
import System.IO (hSetEncoding, stderr, stdout, utf8)
import qualified Text.JSON.Canonical as Canonical
import Text.Show.Pretty (Value (..), parseValue)
import Pos.Util.Json.Canonical (SchemaError (..))
roundTripsAesonYamlShow :: (Eq a, Show a, ToJSON a, FromJSON a) => TestLimit -> Gen a -> Property
roundTripsAesonYamlShow testLimit things = withTests testLimit . property $ do
annotate "Aeson"
forAllWith
(\x -> yamlAesonCustomRender x encode eitherDecode) things >>= roundTripsAesonShow
annotate "Yaml"
forAllWith
(\x -> yamlAesonCustomRender x Y.encode Y.decodeEither') things >>= roundTripsYAMLShow
discoverRoundTrip :: TExpQ Group
discoverRoundTrip = discoverPrefix "roundTrip"
roundTripsAesonShow
:: (Eq a, MonadTest m, ToJSON a, FromJSON a, Show a, HasCallStack) => a -> m ()
roundTripsAesonShow a = tripping a encode eitherDecode
roundTripsYAMLShow
:: (Eq a, MonadTest m, ToJSON a, FromJSON a, Show a) => a -> m ()
roundTripsYAMLShow a = tripping a Y.encode Y.decodeEither'
-- | Round trip any `a` with both `ToJSON` and `FromJSON` instances
roundTripsAesonYamlBuildable
:: (Eq a, MonadTest m, ToJSON a, FromJSON a, Buildable a) => a -> m ()
roundTripsAesonYamlBuildable a = do
trippingBuildable a encode eitherDecode "Aeson"
trippingBuildable a Y.encode Y.decodeEither' "Yaml"
instance Eq Y.ParseException where
_ == _ = False
-- We want @SchemaError@s to show up different (register failure)
instance Eq SchemaError where
_ == _ = False
roundTripsCanonicalJSONShow
:: forall m a
. ( Eq a
, MonadTest m
, Canonical.ToJSON Identity a
, Canonical.FromJSON (Either SchemaError) a
, HasCallStack
, Show a
)
=> a
-> m ()
roundTripsCanonicalJSONShow x =
tripping x (runIdentity . Canonical.toJSON :: a -> Canonical.JSValue)
(Canonical.fromJSON :: Canonical.JSValue -> Either SchemaError a)
runTests :: [IO Bool] -> IO ()
runTests tests' = do
-- ensure UTF-8. As that's what hedgehog needs.
hSetEncoding stdout utf8
hSetEncoding stderr utf8
result <- and <$> sequence tests'
unless result
exitFailure
yamlAesonCustomRender :: (Show a, Show b, Show (f a)) => a -> (a -> b) -> (b -> f a) -> String
yamlAesonCustomRender val enc dec =
let encoded = enc val
decoded = dec encoded
in Prelude.unlines
[ "βββ Original βββ"
, showPretty val
, "βββ Intermediate βββ"
, showPretty encoded
, "βββ Roundtrip βββ"
, showPretty decoded
]
-- | Round trip using given encode and decode functions for types with a
-- `Buildable` instance
trippingBuildable :: (Buildable (f a), Eq (f a), Show b, Applicative f, MonadTest m) => a -> (a -> b) -> (b -> f a) -> String -> m ()
trippingBuildable x enc dec format =
let mx = pure x
i = enc x
my = dec i
in if mx == my
then success
else case valueDiff <$> buildValue mx <*> buildValue my of
Nothing ->
withFrozenCallStack $
failWith Nothing $ Prelude.unlines
[ mconcat ["βββ ", format," βββ"]
, "βββ Original βββ"
, buildPretty mx
, "βββ Intermediate βββ"
, show i
, "βββ Roundtrip βββ"
, buildPretty my
]
Just diff ->
withFrozenCallStack $
failWith
(Just $ Diff "βββ " "- Original" "/" "+ Roundtrip" " βββ" diff) $
Prelude.unlines
[ mconcat ["βββ ", format," βββ"]
, "βββ Intermediate βββ"
, show i
]
instance Buildable a => Buildable (Either Text a) where
build (Left t) = fromText t
build (Right a) = build a
instance Buildable a => Buildable (Either String a) where
build (Left t) = fromString t
build (Right a) = build a
instance Buildable a => Buildable (Either Y.ParseException a) where
build (Left l) = fromText (show l)
build (Right r) = build r
instance Buildable () where
build () = "()"
buildPretty :: Buildable a => a -> String
buildPretty = show . buildValue
buildValue :: Buildable a => a -> Maybe Value
buildValue = parseValue . stringBuild
stringBuild :: Buildable a => a -> String
stringBuild = toString . toLazyText . build
| input-output-hk/pos-haskell-prototype | util/test/Test/Pos/Util/Tripping.hs | Haskell | mit | 5,502 |
{-# OPTIONS_GHC -funbox-strict-fields #-}
{-# LANGUAGE Strict #-}
{-# LANGUAGE StrictData #-}
{-|
Core Noun Implementation
Each cell has a pre-calculated hash and a `size` field. The size is
the total number of nodes under the tree of the cell. This is used
as a heuristic to choose a hash-table size for `jam` and `cue`.
-}
module Urbit.Noun.Core
( Noun, nounSize
, pattern Cell, pattern Atom
, pattern C, pattern A
, textToUtf8Atom, utf8AtomToText
) where
import ClassyPrelude hiding (hash)
import Urbit.Atom
import Data.Bits (xor)
import Data.Function ((&))
import Data.Hashable (hash)
import GHC.Natural (Natural)
import GHC.Prim (reallyUnsafePtrEquality#)
import Test.QuickCheck.Arbitrary (Arbitrary(arbitrary))
import Test.QuickCheck.Gen (Gen, getSize, resize, scale)
import qualified Data.Char as C
-- Types -----------------------------------------------------------------------
data Noun
= NCell Int Word Noun Noun
| NAtom Int Atom
pattern Cell x y <- NCell _ _ x y where Cell = mkCell
pattern Atom a <- NAtom _ a where Atom = mkAtom
{-# COMPLETE Cell, Atom #-}
pattern C x y <- NCell _ _ x y where C = mkCell
pattern A a <- NAtom _ a where A = mkAtom
{-# COMPLETE C, A #-}
--------------------------------------------------------------------------------
instance Hashable Noun where
hash = \case NCell h _ _ _ -> h
NAtom h _ -> h
{-# INLINE hash #-}
hashWithSalt = defaultHashWithSalt
{-# INLINE hashWithSalt #-}
textToUtf8Atom :: Text -> Noun
textToUtf8Atom = Atom . utf8Atom
utf8AtomToText :: Noun -> Either Text Text
utf8AtomToText = \case
Cell _ _ -> Left "Expected @t, but got ^"
Atom atm -> atomUtf8 atm & \case
Left err -> Left (tshow err)
Right tx -> pure tx
instance Show Noun where
show = \case Atom a -> showAtom a
Cell x y -> fmtCell (show <$> (x : toTuple y))
where
fmtCell :: [String] -> String
fmtCell xs = "(" <> intercalate ", " xs <> ")"
toTuple :: Noun -> [Noun]
toTuple (Cell x xs) = x : toTuple xs
toTuple atom = [atom]
showAtom :: Atom -> String
showAtom 0 = "0"
showAtom a | a >= 2^1024 = "\"...\""
showAtom a =
let mTerm = do
t <- utf8AtomToText (Atom a)
let ok = \x -> (C.isPrint x)
if (all ok (t :: Text))
then pure ("\"" <> unpack t <> "\"")
else Left "Don't show as text."
in case mTerm of
Left _ -> show a
Right st -> st
instance Eq Noun where
(==) x y =
case reallyUnsafePtrEquality# x y of
1# -> True
_ -> case (x, y) of
(NAtom x1 a1, NAtom x2 a2) ->
x1 == x2 && a1 == a2
(NCell x1 s1 h1 t1, NCell x2 s2 h2 t2) ->
s1==s2 && x1==x2 && h1==h2 && t1==t2
_ ->
False
{-# INLINE (==) #-}
instance Ord Noun where
compare x y =
case reallyUnsafePtrEquality# x y of
1# -> EQ
_ -> case (x, y) of
(Atom _, Cell _ _) -> LT
(Cell _ _, Atom _) -> GT
(Atom a1, Atom a2) -> compare a1 a2
(Cell h1 t1, Cell h2 t2) -> compare h1 h2 <> compare t1 t2
{-# INLINE compare #-}
instance Arbitrary Noun where
arbitrary = resize 1000 go
where
dub x = Cell x x
go = do
sz <- getSize
(bit, bat :: Bool) <- arbitrary
case (sz, bit, bat) of
( 0, _, _ ) -> Atom <$> genAtom
( _, False, _ ) -> Atom <$> genAtom
( _, True, True ) -> dub <$> arbitrary
( _, True, _ ) -> scale (\x -> x-10) (Cell <$> go <*> go)
genNatural :: Gen Natural
genNatural = fromInteger . abs <$> arbitrary
genAtom :: Gen Atom
genAtom = do
arbitrary >>= \case
False -> genNatural
True -> (`mod` 16) <$> genNatural
--------------------------------------------------------------------------------
{-# INLINE nounSize #-}
nounSize :: Noun -> Word
nounSize = \case
NCell _ s _ _ -> s
NAtom _ _ -> 1
{-# INLINE mkAtom #-}
mkAtom :: Atom -> Noun
mkAtom a = NAtom (hash a) a
{-# INLINE mkCell #-}
mkCell :: Noun -> Noun -> Noun
mkCell h t = NCell has siz h t
where
siz = nounSize h + nounSize t
has = hash h `combine` hash t
-- Stolen from Hashable Library ------------------------------------------------
{-# INLINE combine #-}
combine :: Int -> Int -> Int
combine h1 h2 = (h1 * 16777619) `xor` h2
{-# INLINE defaultHashWithSalt #-}
defaultHashWithSalt :: Hashable a => Int -> a -> Int
defaultHashWithSalt salt x = salt `combine` hash x
| jfranklin9000/urbit | pkg/hs/urbit-king/lib/Urbit/Noun/Core.hs | Haskell | mit | 4,789 |
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeFamilies #-}
-- | Part of GState DB which stores data necessary for update system.
module Pos.DB.Update.GState
(
-- * Getters
getAdoptedBV
, getAdoptedBVData
, getAdoptedBVFull
, getBVState
, getConsensusEra
, getProposalState
, getConfirmedSV
, getMaxBlockSize
, getSlottingData
, getEpochProposers
, getAllProposals
-- * Operations
, UpdateOp (..)
-- * Initialization
, initGStateUS
-- * Iteration and related getters
, PropIter
, getProposalsByApp
, getOldProposals
, getDeepProposals
, ConfPropIter
, getConfirmedProposals
, BVIter
, getProposedBVs
, getCompetingBVStates
, getProposedBVStates
) where
import Universum
import Control.Lens (at)
import Control.Monad.Trans.Resource (ResourceT)
import Data.Conduit (ConduitT, mapOutput, runConduitRes, (.|))
import qualified Data.Conduit.List as CL
import Data.Time.Units (Microsecond, convertUnit)
import qualified Database.RocksDB as Rocks
import Serokell.Data.Memory.Units (Byte)
import UnliftIO (MonadUnliftIO)
import Pos.Binary.Class (serialize')
import Pos.Chain.Genesis as Genesis (Config (..),
configBlockVersionData, configEpochSlots)
import Pos.Chain.Update (ApplicationName, BlockVersion,
BlockVersionData (..), BlockVersionState (..),
ConfirmedProposalState (..), ConsensusEra (..),
DecidedProposalState (dpsDifficulty), NumSoftwareVersion,
ProposalState (..), SoftwareVersion (..),
UndecidedProposalState (upsSlot), UpId,
UpdateConfiguration, UpdateProposal (..), bvsIsConfirmed,
consensusEraBVD, cpsSoftwareVersion, genesisBlockVersion,
genesisSoftwareVersions, ourAppName, ourSystemTag,
psProposal)
import Pos.Core (ChainDifficulty, SlotId, StakeholderId,
TimeDiff (..))
import Pos.Core.Slotting (EpochSlottingData (..), SlottingData,
createInitSlottingData)
import Pos.Crypto (hash)
import Pos.DB (DBIteratorClass (..), DBTag (..), IterType, MonadDB,
MonadDBRead (..), RocksBatchOp (..), encodeWithKeyPrefix)
import Pos.DB.Error (DBError (DBMalformed))
import Pos.DB.GState.Common (gsGetBi, writeBatchGState)
import Pos.Util.Util (maybeThrow)
----------------------------------------------------------------------------
-- Getters
----------------------------------------------------------------------------
-- | Get last adopted block version.
getAdoptedBV :: MonadDBRead m => m BlockVersion
getAdoptedBV = fst <$> getAdoptedBVFull
-- | Get state of last adopted BlockVersion.
getAdoptedBVData :: MonadDBRead m => m BlockVersionData
getAdoptedBVData = snd <$> getAdoptedBVFull
-- | Get last adopted BlockVersion and data associated with it.
getAdoptedBVFull :: MonadDBRead m => m (BlockVersion, BlockVersionData)
getAdoptedBVFull = maybeThrow (DBMalformed msg) =<< getAdoptedBVFullMaybe
where
msg =
"Update System part of GState DB is not initialized (last adopted BV is missing)"
-- | Get the ConsensusEra from the database.
getConsensusEra :: MonadDBRead m => m ConsensusEra
getConsensusEra = consensusEraBVD <$> getAdoptedBVData
-- | Get maximum block size (in bytes).
getMaxBlockSize :: MonadDBRead m => m Byte
getMaxBlockSize = bvdMaxBlockSize <$> getAdoptedBVData
-- | Get 'BlockVersionState' associated with given BlockVersion.
getBVState :: MonadDBRead m => BlockVersion -> m (Maybe BlockVersionState)
getBVState = gsGetBi . bvStateKey
-- | Get state of UpdateProposal for given UpId
getProposalState :: (MonadDBRead m) => UpId -> m (Maybe ProposalState)
getProposalState = gsGetBi . proposalKey
-- | Get last confirmed SoftwareVersion of given application.
getConfirmedSV :: MonadDBRead m => ApplicationName -> m (Maybe NumSoftwareVersion)
getConfirmedSV = gsGetBi . confirmedVersionKey
-- | Get most recent 'SlottingData'.
getSlottingData :: MonadDBRead m => m SlottingData
getSlottingData = maybeThrow (DBMalformed msg) =<< gsGetBi slottingDataKey
where
msg = "Update System part of GState DB is not initialized (slotting data is missing)"
-- | Get proposers for current epoch.
getEpochProposers :: MonadDBRead m => m (HashSet StakeholderId)
getEpochProposers = maybeThrow (DBMalformed msg) =<< gsGetBi epochProposersKey
where
msg =
"Update System part of GState DB is not initialized (epoch proposers are missing)"
----------------------------------------------------------------------------
-- Operations
----------------------------------------------------------------------------
data UpdateOp
= PutProposal !ProposalState
| DeleteProposal !UpId
| ConfirmVersion !SoftwareVersion
| DelConfirmedVersion !ApplicationName
| AddConfirmedProposal !ConfirmedProposalState
| DelConfirmedProposal !SoftwareVersion
| SetAdopted !BlockVersion BlockVersionData
| SetBVState !BlockVersion !BlockVersionState
| DelBV !BlockVersion
| PutSlottingData !SlottingData
| PutEpochProposers !(HashSet StakeholderId)
instance RocksBatchOp UpdateOp where
toBatchOp (PutProposal ps) =
[ Rocks.Put (proposalKey upId) (serialize' ps)]
where
up = psProposal ps
upId = hash up
toBatchOp (DeleteProposal upId) =
[Rocks.Del (proposalKey upId)]
toBatchOp (ConfirmVersion sv) =
[Rocks.Put (confirmedVersionKey $ svAppName sv) (serialize' $ svNumber sv)]
toBatchOp (DelConfirmedVersion app) =
[Rocks.Del (confirmedVersionKey app)]
toBatchOp (AddConfirmedProposal cps) =
[Rocks.Put (confirmedProposalKey cps) (serialize' cps)]
toBatchOp (DelConfirmedProposal sv) =
[Rocks.Del (confirmedProposalKeySV sv)]
toBatchOp (SetAdopted bv bvd) =
[Rocks.Put adoptedBVKey (serialize' (bv, bvd))]
toBatchOp (SetBVState bv st) =
[Rocks.Put (bvStateKey bv) (serialize' st)]
toBatchOp (DelBV bv) =
[Rocks.Del (bvStateKey bv)]
toBatchOp (PutSlottingData sd) =
[Rocks.Put slottingDataKey (serialize' sd)]
toBatchOp (PutEpochProposers proposers) =
[Rocks.Put epochProposersKey (serialize' proposers)]
----------------------------------------------------------------------------
-- Initialization
----------------------------------------------------------------------------
initGStateUS :: MonadDB m => Genesis.Config -> m ()
initGStateUS genesisConfig = do
writeBatchGState $
PutSlottingData genesisSlottingData :
PutEpochProposers mempty :
SetAdopted genesisBlockVersion genesisBvd :
map ConfirmVersion genesisSoftwareVersions
where
genesisBvd = configBlockVersionData genesisConfig
genesisSlotDuration = bvdSlotDuration genesisBvd
genesisEpochDuration :: Microsecond
genesisEpochDuration = fromIntegral (configEpochSlots genesisConfig) * convertUnit genesisSlotDuration
esdCurrent :: EpochSlottingData
esdCurrent = EpochSlottingData
{ esdSlotDuration = genesisSlotDuration
, esdStartDiff = 0
}
esdNext :: EpochSlottingData
esdNext = EpochSlottingData
{ esdSlotDuration = genesisSlotDuration
, esdStartDiff = TimeDiff genesisEpochDuration
}
genesisSlottingData :: SlottingData
genesisSlottingData = createInitSlottingData esdCurrent esdNext
----------------------------------------------------------------------------
-- Iteration
----------------------------------------------------------------------------
data PropIter
-- proposals added by PutProposal, and removed by DeleteProposal
-- upModifierToBatch takes a list of proposals to add&delete
-- listed via getAllProposals, getOldProposals, getDeepProposals, getProposalsByApp
-- does not contain confirmed proposals
instance DBIteratorClass PropIter where
type IterKey PropIter = UpId
type IterValue PropIter = ProposalState
iterKeyPrefix = iterationPrefix
proposalSource ::
(MonadDBRead m)
=> ConduitT () (IterType PropIter) (ResourceT m) ()
proposalSource = dbIterSource GStateDB (Proxy @PropIter)
getAllProposals :: (MonadDBRead m, MonadUnliftIO m) => m [(UpId, ProposalState)]
getAllProposals = do
runConduitRes $ proposalSource .| CL.consume
-- TODO: it can be optimized by storing some index sorted by
-- 'SlotId's, but I don't think it may be crucial.
-- | Get all proposals which were issued no later than given slot.
getOldProposals
:: (MonadDBRead m, MonadUnliftIO m)
=> SlotId -> m [UndecidedProposalState]
getOldProposals slotId =
runConduitRes $ mapOutput snd proposalSource .| CL.mapMaybe isOld .| CL.consume
where
isOld (PSUndecided u) | upsSlot u <= slotId = Just u
isOld _ = Nothing
-- | Get all decided proposals which were accepted deeper than given
-- difficulty.
getDeepProposals
:: (MonadDBRead m, MonadUnliftIO m)
=> ChainDifficulty -> m [DecidedProposalState]
getDeepProposals cd =
runConduitRes $ mapOutput snd proposalSource .| CL.mapMaybe isDeep .| CL.consume
where
isDeep e | PSDecided u <- e
, Just proposalDifficulty <- dpsDifficulty u
, proposalDifficulty <= cd = Just u
isDeep _ = Nothing
-- | Get states of all competing 'UpdateProposal's for given 'ApplicationName'.
getProposalsByApp ::
(MonadDBRead m, MonadUnliftIO m)
=> ApplicationName
-> m [ProposalState]
getProposalsByApp appName =
runConduitRes $ mapOutput snd proposalSource .| CL.filter matchesName .| CL.consume
where
matchesName e = appName == (svAppName $ upSoftwareVersion $ psProposal e)
-- Iterator by confirmed proposals
data ConfPropIter
instance DBIteratorClass ConfPropIter where
type IterKey ConfPropIter = SoftwareVersion
type IterValue ConfPropIter = ConfirmedProposalState
iterKeyPrefix = confirmedIterationPrefix
-- | Get confirmed proposals which update our application
-- (i. e. application name matches our application name and there is
-- update data for our system tag) and have version greater than
-- argument. Intended usage is to pass numberic version of this
-- software as argument.
-- Returns __all__ confirmed proposals if the argument is 'Nothing'.
getConfirmedProposals
:: (MonadDBRead m, MonadUnliftIO m)
=> UpdateConfiguration
-> Maybe NumSoftwareVersion
-> m [ConfirmedProposalState]
getConfirmedProposals uc reqNsv =
runConduitRes $
dbIterSource GStateDB (Proxy @ConfPropIter) .| CL.mapMaybe onItem .|
CL.consume
where
onItem (SoftwareVersion {..}, cps)
| Nothing <- reqNsv = Just cps
| Just v <- reqNsv
, hasOurSystemTag cps && svAppName == ourAppName uc && svNumber > v =
Just cps
| otherwise = Nothing
hasOurSystemTag ConfirmedProposalState {..} =
isJust $ upData cpsUpdateProposal ^. at (ourSystemTag uc)
-- Iterator by block versions
data BVIter
instance DBIteratorClass BVIter where
type IterKey BVIter = BlockVersion
type IterValue BVIter = BlockVersionState
iterKeyPrefix = bvStateIterationPrefix
bvSource :: (MonadDBRead m) => ConduitT () (IterType BVIter) (ResourceT m) ()
bvSource = dbIterSource GStateDB (Proxy @BVIter)
-- | Get all proposed 'BlockVersion's.
getProposedBVs :: (MonadDBRead m, MonadUnliftIO m) => m [BlockVersion]
getProposedBVs = runConduitRes $ mapOutput fst bvSource .| CL.consume
getProposedBVStates :: (MonadDBRead m, MonadUnliftIO m) => m [BlockVersionState]
getProposedBVStates = runConduitRes $ mapOutput snd bvSource .| CL.consume
-- | Get all competing 'BlockVersion's and their states.
getCompetingBVStates
:: (MonadDBRead m, MonadUnliftIO m)
=> m [(BlockVersion, BlockVersionState)]
getCompetingBVStates =
runConduitRes $ bvSource .| CL.filter (bvsIsConfirmed . snd) .| CL.consume
----------------------------------------------------------------------------
-- Keys ('us' prefix stands for Update System)
----------------------------------------------------------------------------
adoptedBVKey :: ByteString
adoptedBVKey = "us/adopted-block-version/"
bvStateKey :: BlockVersion -> ByteString
bvStateKey = encodeWithKeyPrefix @BVIter
bvStateIterationPrefix :: ByteString
bvStateIterationPrefix = "us/bvs/"
proposalKey :: UpId -> ByteString
proposalKey = encodeWithKeyPrefix @PropIter
confirmedVersionKey :: ApplicationName -> ByteString
confirmedVersionKey = mappend "us/cv/" . serialize'
iterationPrefix :: ByteString
iterationPrefix = "us/p/"
confirmedProposalKey :: ConfirmedProposalState -> ByteString
confirmedProposalKey = encodeWithKeyPrefix @ConfPropIter . cpsSoftwareVersion
confirmedProposalKeySV :: SoftwareVersion -> ByteString
confirmedProposalKeySV = encodeWithKeyPrefix @ConfPropIter
confirmedIterationPrefix :: ByteString
confirmedIterationPrefix = "us/cp/"
slottingDataKey :: ByteString
slottingDataKey = "us/slotting/"
epochProposersKey :: ByteString
epochProposersKey = "us/epoch-proposers/"
----------------------------------------------------------------------------
-- Details
----------------------------------------------------------------------------
getAdoptedBVFullMaybe
:: MonadDBRead m
=> m (Maybe (BlockVersion, BlockVersionData))
getAdoptedBVFullMaybe = gsGetBi adoptedBVKey
| input-output-hk/pos-haskell-prototype | db/src/Pos/DB/Update/GState.hs | Haskell | mit | 13,678 |
{-# LANGUAGE CPP #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
-- | Auxx plugin.
module Plugin
( auxxPlugin
, rawExec
) where
import Universum
#if !(defined(mingw32_HOST_OS))
import System.Exit (ExitCode (ExitSuccess))
import System.Posix.Process (exitImmediately)
#endif
import Control.Monad.Except (ExceptT (..), withExceptT)
import Data.Constraint (Dict (..))
import Data.Time.Units (Second)
import Formatting (float, int, sformat, (%))
import System.IO (hFlush, stdout)
import Pos.Chain.Genesis as Genesis (Config (..))
import Pos.Chain.Txp (TxpConfiguration, genesisUtxo)
import Pos.Core.Conc (delay)
import Pos.Crypto (AHash (..), fullPublicKeyF, hashHexF)
import Pos.Infra.Diffusion.Types (Diffusion)
import Pos.Util.Wlog (CanLog, HasLoggerName, logInfo)
import AuxxOptions (AuxxOptions (..))
import Command (createCommandProcs)
import qualified Lang
import Mode (MonadAuxxMode)
import Repl (PrintAction, WithCommandAction (..))
----------------------------------------------------------------------------
-- Plugin implementation
----------------------------------------------------------------------------
{-# ANN module ("HLint: ignore Reduce duplication" :: Text) #-}
auxxPlugin ::
MonadAuxxMode m
=> Genesis.Config
-> TxpConfiguration
-> AuxxOptions
-> Either WithCommandAction Text
-> Diffusion m
-> m ()
auxxPlugin genesisConfig txpConfig auxxOptions repl = \diffusion -> do
logInfo $ sformat ("Length of genesis utxo: " %int)
(length $ genesisUtxo $ configGenesisData genesisConfig)
rawExec (Just genesisConfig) (Just txpConfig) (Just Dict) auxxOptions (Just diffusion) repl
rawExec ::
( MonadIO m
, MonadCatch m
, CanLog m
, HasLoggerName m
)
=> Maybe Genesis.Config
-> Maybe TxpConfiguration
-> Maybe (Dict (MonadAuxxMode m))
-> AuxxOptions
-> Maybe (Diffusion m)
-> Either WithCommandAction Text
-> m ()
rawExec mCoreConfig txpConfig mHasAuxxMode AuxxOptions{..} mDiffusion = \case
Left WithCommandAction{..} -> do
printAction "... the auxx plugin is ready"
forever $ withCommand $ runCmd mCoreConfig txpConfig mHasAuxxMode mDiffusion printAction
Right cmd -> runWalletCmd mCoreConfig txpConfig mHasAuxxMode mDiffusion cmd
runWalletCmd ::
( MonadIO m
, CanLog m
, HasLoggerName m
)
=> Maybe Genesis.Config
-> Maybe TxpConfiguration
-> Maybe (Dict (MonadAuxxMode m))
-> Maybe (Diffusion m)
-> Text
-> m ()
runWalletCmd mCoreConfig txpConfig mHasAuxxMode mDiffusion line = do
runCmd mCoreConfig txpConfig mHasAuxxMode mDiffusion printAction line
printAction "Command execution finished"
printAction " " -- for exit by SIGPIPE
liftIO $ hFlush stdout
#if !(defined(mingw32_HOST_OS))
delay (3 :: Second)
liftIO $ exitImmediately ExitSuccess
#endif
where
printAction = putText
runCmd ::
( MonadIO m
, CanLog m
, HasLoggerName m
)
=> Maybe Genesis.Config
-> Maybe TxpConfiguration
-> Maybe (Dict (MonadAuxxMode m))
-> Maybe (Diffusion m)
-> PrintAction m
-> Text
-> m ()
runCmd mCoreConfig txpConfig mHasAuxxMode mDiffusion printAction line = do
let commandProcs = createCommandProcs mCoreConfig
txpConfig
mHasAuxxMode
printAction
mDiffusion
parse = withExceptT Lang.ppParseError . ExceptT . return . Lang.parse
resolveCommandProcs =
withExceptT Lang.ppResolveErrors . ExceptT . return .
Lang.resolveCommandProcs commandProcs
evaluate = withExceptT Lang.ppEvalError . ExceptT . Lang.evaluate
pipeline = parse >=> resolveCommandProcs >=> evaluate
runExceptT (pipeline line) >>= \case
Left errDoc -> printAction (Lang.renderAuxxDoc errDoc)
Right value -> withValueText printAction value
withValueText :: Monad m => (Text -> m ()) -> Lang.Value -> m ()
withValueText cont = \case
Lang.ValueUnit -> return ()
Lang.ValueNumber n -> cont (sformat float n)
Lang.ValueString s -> cont (toText s)
Lang.ValueBool b -> cont (pretty b)
Lang.ValueAddress a -> cont (pretty a)
Lang.ValuePublicKey pk -> cont (sformat fullPublicKeyF pk)
Lang.ValueTxOut txOut -> cont (pretty txOut)
Lang.ValueStakeholderId sId -> cont (sformat hashHexF sId)
Lang.ValueHash h -> cont (sformat hashHexF (getAHash h))
Lang.ValueBlockVersion v -> cont (pretty v)
Lang.ValueSoftwareVersion v -> cont (pretty v)
Lang.ValueBlockVersionModifier bvm -> cont (pretty bvm)
Lang.ValueBlockVersionData bvd -> cont (pretty bvd)
Lang.ValueProposeUpdateSystem pus -> cont (show pus)
Lang.ValueAddrDistrPart adp -> cont (show adp)
Lang.ValueAddrStakeDistribution asd -> cont (pretty asd)
Lang.ValueFilePath s -> cont (toText s)
Lang.ValueList vs -> for_ vs $
withValueText (cont . mappend " ")
----------------------------------------------------------------------------
-- Extra logging
----------------------------------------------------------------------------
-- This addLogging was misplaced to begin with.
-- A debug-mode diffusion layer could be chosen, which logs absolutely all
-- network activity. But surely for auxx logging, the logging should go around
-- the high-level auxx commands, no?
{-
addLogging :: forall m. WithLogger m => SendActions m -> SendActions m
addLogging SendActions{..} = SendActions{
enqueueMsg = error "unused"
, withConnectionTo = aux
}
where
aux nid k = withConnectionTo nid $ \peerData -> fmap auxConv (k peerData)
auxConv (Conversation k) = Conversation (\acts -> k (auxActs acts))
auxActs :: (Message snd, Message rcv)
=> ConversationActions snd rcv m -> ConversationActions snd rcv m
auxActs (ConversationActions{..}) = ConversationActions {
send = \body -> do
logDebug $ sformat ("Auxx sending " % stext) (formatMessage body)
send body
, recv = \limit -> do
mRcv <- recv limit
logDebug $
case mRcv of
Nothing -> sformat ("Auxx received end of input")
Just rcv -> sformat ("Auxx received " % stext) (formatMessage rcv)
return mRcv
, sendRaw = sendRaw
}
-}
| input-output-hk/pos-haskell-prototype | auxx/src/Plugin.hs | Haskell | mit | 6,746 |
-- We need 'FlexibleInstances to instance 'ArgVal' for 'Maybe Exp' and
-- '( String, Exp )'.
{-# LANGUAGE FlexibleInstances #-}
module Arith where
import Prelude hiding ( exp )
import System.Console.CmdTheLine hiding ( eval )
import Control.Applicative hiding ( (<|>) )
import Control.Monad ( guard )
import Data.Char ( isAlpha )
import Data.Function ( on )
import Text.Parsec
import qualified Text.PrettyPrint as PP
import qualified Data.Map as M
import System.IO
type Parser a = Parsec String () a
data Bin = Pow | Mul | Div | Add | Sub
prec :: Bin -> Int
prec b = case b of
{ Pow -> 3 ; Mul -> 2 ; Div -> 2 ; Add -> 1 ; Sub -> 1 }
assoc :: Bin -> Assoc
assoc b = case b of
Pow -> R
_ -> L
toFunc :: Bin -> (Int -> Int -> Int)
toFunc b = case b of
{ Pow -> (^) ; Mul -> (*) ; Div -> div ; Add -> (+) ; Sub -> (-) }
data Exp = IntExp Int
| VarExp String
| BinExp Bin Exp Exp
instance ArgVal Exp where
converter = ( parser, pretty 0 )
where
parser = fromParsec onErr exp
onErr str = PP.text "invalid expression" PP.<+> PP.quotes (PP.text str)
instance ArgVal (Maybe Exp) where
converter = just
instance ArgVal ( String, Exp ) where
converter = pair '='
data Assoc = L | R
type Env = M.Map String Exp
catParsers :: [Parser String] -> Parser String
catParsers = foldl (liftA2 (++)) (return "")
integer :: Parser Int
integer = read <$> catParsers [ option "" $ string "-", many1 digit ]
tok :: Parser a -> Parser a
tok p = p <* spaces
parens :: Parser a -> Parser a
parens = between op cp
where
op = tok $ char '('
cp = tok $ char ')'
-- Parse a terminal expression.
term :: Parser Exp
term = parens exp <|> int <|> var
where
int = tok $ IntExp <$> try integer -- Try so '-<not-digits>' won't fail.
var = tok $ VarExp <$> many1 (satisfy isAlpha)
-- Parse a binary operator.
bin :: Parser Bin
bin = choice [ pow, mul, div, add, sub ]
where
pow = tok $ Pow <$ char '^'
mul = tok $ Mul <$ char '*'
div = tok $ Div <$ char '/'
add = tok $ Add <$ char '+'
sub = tok $ Sub <$ char '-'
exp :: Parser Exp
exp = e 0
-- Precedence climbing expressions. See
-- <www.engr.mun.ca/~theo/Misc/exp_parsing.htm> for further information.
e :: Int -> Parser Exp
e p = do
t <- term
try (go t) <|> return t
where
go e1 = do
b <- bin
guard $ prec b >= p
let q = case assoc b of
R -> prec b
L -> prec b + 1
e2 <- e q
let expr = BinExp b e1 e2
try (go expr) <|> return expr
-- Beta reduce by replacing variables in 'e' with values in 'env'.
beta :: Env -> Exp -> Maybe Exp
beta env e = case e of
VarExp str -> M.lookup str env
int@(IntExp _) -> return int
BinExp b e1 e2 -> (liftA2 (BinExp b) `on` beta env) e1 e2
eval :: Exp -> Int
eval e = case e of
VarExp str -> error $ "saw VarExp " ++ str ++ " while evaluating"
IntExp i -> i
BinExp b e1 e2 -> (toFunc b `on` eval) e1 e2
pretty :: Int -> Exp -> PP.Doc
pretty p e = case e of
VarExp str -> PP.text str
IntExp i -> PP.int i
BinExp b e1 e2 -> let q = prec b
in parensOrNot q $ PP.cat [ pretty q e1, ppBin b, pretty q e2 ]
where
parensOrNot q = if q < p then PP.parens else id
ppBin :: Bin -> PP.Doc
ppBin b = case b of
Pow -> PP.char '^'
Mul -> PP.char '*'
Div -> PP.char '/'
Add -> PP.char '+'
Sub -> PP.char '-'
arith :: Bool -> [( String, Exp )] -> Exp -> IO ()
arith pp assoc = maybe badEnv method . beta (M.fromList assoc)
where
method = if pp then print . pretty 0 else print . eval
badEnv = hPutStrLn stderr "arith: bad environment"
arithTerm :: Term (IO ())
arithTerm = arith <$> pp <*> env <*> e
where
pp = value $ flag (optInfo [ "pretty", "p" ])
{ optName = "PP"
, optDoc = "If present, pretty print instead of evaluating EXP."
}
env = nonEmpty $ posRight 0 [] posInfo
{ posName = "ENV"
, posDoc = "One or more assignments of the form '<name>=<exp>' to be "
++ "substituted in the input expression."
}
e = required $ pos 0 Nothing posInfo
{ posName = "EXP"
, posDoc = "An arithmetic expression to be evaluated."
}
termInfo :: TermInfo
termInfo = defTI
{ termName = "arith"
, version = "0.3"
, termDoc = "Evaluate mathematical functions demonstrating precedence "
++ "climbing and instantiating 'ArgVal' for tuples and Parsec "
++ "parsers."
, man = [ S "BUGS"
, P "Email bug reports to <[email protected]>"
]
}
| glutamate/cmdtheline | test/Arith.hs | Haskell | mit | 4,544 |
<?xml version="1.0" encoding="UTF-8"?>
<!DOCTYPE helpset PUBLIC "-//Sun Microsystems Inc.//DTD JavaHelp HelpSet Version 2.0//EN" "http://java.sun.com/products/javahelp/helpset_2_0.dtd">
<helpset version="2.0" xml:lang="zh-CN">
<title>Authentication Statistics | ZAP Extension</title>
<maps>
<homeID>top</homeID>
<mapref location="map.jhm"/>
</maps>
<view>
<name>TOC</name>
<label>Contents</label>
<type>org.zaproxy.zap.extension.help.ZapTocView</type>
<data>toc.xml</data>
</view>
<view>
<name>Index</name>
<label>Index</label>
<type>javax.help.IndexView</type>
<data>index.xml</data>
</view>
<view>
<name>Search</name>
<label>Search</label>
<type>javax.help.SearchView</type>
<data engine="com.sun.java.help.search.DefaultSearchEngine">
JavaHelpSearch
</data>
</view>
<view>
<name>Favorites</name>
<label>Favorites</label>
<type>javax.help.FavoritesView</type>
</view>
</helpset> | veggiespam/zap-extensions | addOns/authstats/src/main/javahelp/org/zaproxy/zap/extension/authstats/resources/help_zh_CN/helpset_zh_CN.hs | Haskell | apache-2.0 | 987 |
{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TupleSections #-}
-- | Test suite for Stack.Dot
module Stack.DotSpec where
import Control.Monad (filterM)
import Data.Foldable as F
import Data.Functor.Identity
import Data.List ((\\))
import qualified Data.Map as Map
import Data.Maybe (fromMaybe)
import Data.Set (Set)
import qualified Data.Set as Set
import Data.Text (Text)
import Stack.Types.PackageName
import Stack.Types.Version
import Test.Hspec
import Test.Hspec.QuickCheck (prop)
import Test.QuickCheck (forAll,choose,Gen)
import Stack.Dot
dummyVersion :: Version
dummyVersion = fromMaybe (error "dotspec: parser error") (parseVersionFromString "0.0.0.0")
spec :: Spec
spec = do
let graph =
Map.mapKeys pkgName
. fmap (\p -> (Set.map pkgName p, Just dummyVersion))
. Map.fromList $ [("one",Set.fromList ["base","free"])
,("two",Set.fromList ["base","free","mtl","transformers","one"])
]
describe "Stack.Dot" $ do
it "does nothing if depth is 0" $
resolveDependencies (Just 0) graph stubLoader `shouldBe` return graph
it "with depth 1, more dependencies are resolved" $ do
let graph' = Map.insert (pkgName "cycle")
(Set.singleton (pkgName "cycle"), Just dummyVersion)
graph
resultGraph = runIdentity (resolveDependencies (Just 0) graph stubLoader)
resultGraph' = runIdentity (resolveDependencies (Just 1) graph' stubLoader)
Map.size resultGraph < Map.size resultGraph' `shouldBe` True
it "cycles are ignored" $ do
let graph' = Map.insert (pkgName "cycle")
(Set.singleton (pkgName "cycle"), Just dummyVersion)
graph
resultGraph = resolveDependencies Nothing graph stubLoader
resultGraph' = resolveDependencies Nothing graph' stubLoader
fmap Map.size resultGraph' `shouldBe` fmap ((+1) . Map.size) resultGraph
let graphElem e = Set.member e . Set.unions . Map.elems
prop "requested packages are pruned" $ do
let resolvedGraph = runIdentity (resolveDependencies Nothing graph stubLoader)
allPackages g = Set.map show (Map.keysSet g `Set.union` F.fold (fmap fst g))
forAll (sublistOf (Set.toList (allPackages resolvedGraph))) $ \toPrune ->
let pruned = pruneGraph [pkgName "one", pkgName "two"] toPrune resolvedGraph
in Set.null (allPackages pruned `Set.intersection` Set.fromList toPrune)
prop "pruning removes orhpans" $ do
let resolvedGraph = runIdentity (resolveDependencies Nothing graph stubLoader)
allPackages g = Set.map show (Map.keysSet g `Set.union` F.fold (fmap fst g))
orphans g = Map.filterWithKey (\k _ -> not (graphElem k g)) g
forAll (sublistOf (Set.toList (allPackages resolvedGraph))) $ \toPrune ->
let pruned = pruneGraph [pkgName "one", pkgName "two"] toPrune resolvedGraph
in null (Map.keys (orphans (fmap fst pruned)) \\ [pkgName "one", pkgName "two"])
{- Helper functions below -}
-- Backport from QuickCheck 2.8 to 2.7.6
sublistOf :: [a] -> Gen [a]
sublistOf = filterM (\_ -> choose (False, True))
-- Unsafe internal helper to create a package name
pkgName :: Text -> PackageName
pkgName = fromMaybe failure . parsePackageName
where
failure = error "Internal error during package name creation in DotSpec.pkgName"
-- Stub, simulates the function to load package dependecies
stubLoader :: PackageName -> Identity (Set PackageName, Maybe Version)
stubLoader name = return . (, Just dummyVersion) . Set.fromList . map pkgName $ case show name of
"StateVar" -> ["stm","transformers"]
"array" -> []
"bifunctors" -> ["semigroupoids","semigroups","tagged"]
"binary" -> ["array","bytestring","containers"]
"bytestring" -> ["deepseq","ghc-prim","integer-gmp"]
"comonad" -> ["containers","contravariant","distributive"
,"semigroups","tagged","transformers","transformers-compat"
]
"cont" -> ["StateVar","semigroups","transformers","transformers-compat","void"]
"containers" -> ["array","deepseq","ghc-prim"]
"deepseq" -> ["array"]
"distributive" -> ["ghc-prim","tagged","transformers","transformers-compat"]
"free" -> ["bifunctors","comonad","distributive","mtl"
,"prelude-extras","profunctors","semigroupoids"
,"semigroups","template-haskell","transformers"
]
"ghc" -> []
"hashable" -> ["bytestring","ghc-prim","integer-gmp","text"]
"integer" -> []
"mtl" -> ["transformers"]
"nats" -> []
"one" -> ["free"]
"prelude" -> []
"profunctors" -> ["comonad","distributive","semigroupoids","tagged","transformers"]
"semigroupoids" -> ["comonad","containers","contravariant","distributive"
,"semigroups","transformers","transformers-compat"
]
"semigroups" -> ["bytestring","containers","deepseq","hashable"
,"nats","text","unordered-containers"
]
"stm" -> ["array"]
"tagged" -> ["template-haskell"]
"template" -> []
"text" -> ["array","binary","bytestring","deepseq","ghc-prim","integer-gmp"]
"transformers" -> []
"two" -> ["free","mtl","one","transformers"]
"unordered" -> ["deepseq","hashable"]
"void" -> ["ghc-prim","hashable","semigroups"]
_ -> []
| AndrewRademacher/stack | src/test/Stack/DotSpec.hs | Haskell | bsd-3-clause | 5,515 |
import Test.HUnit (Assertion, (@=?), runTestTT, Test(..), Counts(..))
import System.Exit (ExitCode(..), exitWith)
import Prime (nth)
exitProperly :: IO Counts -> IO ()
exitProperly m = do
counts <- m
exitWith $ if failures counts /= 0 || errors counts /= 0 then ExitFailure 1 else ExitSuccess
testCase :: String -> Assertion -> Test
testCase label assertion = TestLabel label (TestCase assertion)
main :: IO ()
main = exitProperly $ runTestTT $ TestList
[ TestList primeTests ]
primeTests :: [Test]
primeTests = map TestCase
[ 2 @=? nth 1
, 3 @=? nth 2
, 13 @=? nth 6
, [2,3,5,7,11,13,17,19,23,29,31,37,41,43,47,53,59,61,67,71] @=?
map nth [1..20]
, 7919 @=? nth 1000
, 104729 @=? nth 10000
, 104743 @=? nth 10001
]
| pminten/xhaskell | nth-prime/nth-prime_test.hs | Haskell | mit | 751 |
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveGeneric #-}
-----------------------------------------------------------------------------
-- |
-- Module : Distribution.Simple.Program.Db
-- Copyright : Isaac Jones 2006, Duncan Coutts 2007-2009
--
-- Maintainer : [email protected]
-- Portability : portable
--
-- This provides a 'ProgramDb' type which holds configured and not-yet
-- configured programs. It is the parameter to lots of actions elsewhere in
-- Cabal that need to look up and run programs. If we had a Cabal monad,
-- the 'ProgramDb' would probably be a reader or state component of it.
--
-- One nice thing about using it is that any program that is
-- registered with Cabal will get some \"configure\" and \".cabal\"
-- helpers like --with-foo-args --foo-path= and extra-foo-args.
--
-- There's also a hook for adding programs in a Setup.lhs script. See
-- hookedPrograms in 'Distribution.Simple.UserHooks'. This gives a
-- hook user the ability to get the above flags and such so that they
-- don't have to write all the PATH logic inside Setup.lhs.
module Distribution.Simple.Program.Db (
-- * The collection of configured programs we can run
ProgramDb,
emptyProgramDb,
defaultProgramDb,
restoreProgramDb,
-- ** Query and manipulate the program db
addKnownProgram,
addKnownPrograms,
lookupKnownProgram,
knownPrograms,
getProgramSearchPath,
setProgramSearchPath,
modifyProgramSearchPath,
userSpecifyPath,
userSpecifyPaths,
userMaybeSpecifyPath,
userSpecifyArgs,
userSpecifyArgss,
userSpecifiedArgs,
lookupProgram,
updateProgram,
configuredPrograms,
-- ** Query and manipulate the program db
configureProgram,
configureAllKnownPrograms,
lookupProgramVersion,
reconfigurePrograms,
requireProgram,
requireProgramVersion,
) where
import Distribution.Simple.Program.Types
( Program(..), ProgArg, ConfiguredProgram(..), ProgramLocation(..) )
import Distribution.Simple.Program.Find
( ProgramSearchPath, defaultProgramSearchPath
, findProgramOnSearchPath, programSearchPathAsPATHVar )
import Distribution.Simple.Program.Builtin
( builtinPrograms )
import Distribution.Simple.Utils
( die, doesExecutableExist )
import Distribution.Version
( Version, VersionRange, isAnyVersion, withinRange )
import Distribution.Text
( display )
import Distribution.Verbosity
( Verbosity )
import Distribution.Compat.Binary (Binary(..))
#if __GLASGOW_HASKELL__ < 710
import Data.Functor ((<$>))
#endif
import Data.List
( foldl' )
import Data.Maybe
( catMaybes )
import qualified Data.Map as Map
import Control.Monad
( join, foldM )
-- ------------------------------------------------------------
-- * Programs database
-- ------------------------------------------------------------
-- | The configuration is a collection of information about programs. It
-- contains information both about configured programs and also about programs
-- that we are yet to configure.
--
-- The idea is that we start from a collection of unconfigured programs and one
-- by one we try to configure them at which point we move them into the
-- configured collection. For unconfigured programs we record not just the
-- 'Program' but also any user-provided arguments and location for the program.
data ProgramDb = ProgramDb {
unconfiguredProgs :: UnconfiguredProgs,
progSearchPath :: ProgramSearchPath,
configuredProgs :: ConfiguredProgs
}
type UnconfiguredProgram = (Program, Maybe FilePath, [ProgArg])
type UnconfiguredProgs = Map.Map String UnconfiguredProgram
type ConfiguredProgs = Map.Map String ConfiguredProgram
emptyProgramDb :: ProgramDb
emptyProgramDb = ProgramDb Map.empty defaultProgramSearchPath Map.empty
defaultProgramDb :: ProgramDb
defaultProgramDb = restoreProgramDb builtinPrograms emptyProgramDb
-- internal helpers:
updateUnconfiguredProgs :: (UnconfiguredProgs -> UnconfiguredProgs)
-> ProgramDb -> ProgramDb
updateUnconfiguredProgs update conf =
conf { unconfiguredProgs = update (unconfiguredProgs conf) }
updateConfiguredProgs :: (ConfiguredProgs -> ConfiguredProgs)
-> ProgramDb -> ProgramDb
updateConfiguredProgs update conf =
conf { configuredProgs = update (configuredProgs conf) }
-- Read & Show instances are based on listToFM
-- Note that we only serialise the configured part of the database, this is
-- because we don't need the unconfigured part after the configure stage, and
-- additionally because we cannot read/show 'Program' as it contains functions.
instance Show ProgramDb where
show = show . Map.toAscList . configuredProgs
instance Read ProgramDb where
readsPrec p s =
[ (emptyProgramDb { configuredProgs = Map.fromList s' }, r)
| (s', r) <- readsPrec p s ]
instance Binary ProgramDb where
put = put . configuredProgs
get = do
progs <- get
return $! emptyProgramDb { configuredProgs = progs }
-- | The Read\/Show instance does not preserve all the unconfigured 'Programs'
-- because 'Program' is not in Read\/Show because it contains functions. So to
-- fully restore a deserialised 'ProgramDb' use this function to add
-- back all the known 'Program's.
--
-- * It does not add the default programs, but you probably want them, use
-- 'builtinPrograms' in addition to any extra you might need.
--
restoreProgramDb :: [Program] -> ProgramDb -> ProgramDb
restoreProgramDb = addKnownPrograms
-- -------------------------------
-- Managing unconfigured programs
-- | Add a known program that we may configure later
--
addKnownProgram :: Program -> ProgramDb -> ProgramDb
addKnownProgram prog = updateUnconfiguredProgs $
Map.insertWith combine (programName prog) (prog, Nothing, [])
where combine _ (_, path, args) = (prog, path, args)
addKnownPrograms :: [Program] -> ProgramDb -> ProgramDb
addKnownPrograms progs conf = foldl' (flip addKnownProgram) conf progs
lookupKnownProgram :: String -> ProgramDb -> Maybe Program
lookupKnownProgram name =
fmap (\(p,_,_)->p) . Map.lookup name . unconfiguredProgs
knownPrograms :: ProgramDb -> [(Program, Maybe ConfiguredProgram)]
knownPrograms conf =
[ (p,p') | (p,_,_) <- Map.elems (unconfiguredProgs conf)
, let p' = Map.lookup (programName p) (configuredProgs conf) ]
-- | Get the current 'ProgramSearchPath' used by the 'ProgramDb'.
-- This is the default list of locations where programs are looked for when
-- configuring them. This can be overridden for specific programs (with
-- 'userSpecifyPath'), and specific known programs can modify or ignore this
-- search path in their own configuration code.
--
getProgramSearchPath :: ProgramDb -> ProgramSearchPath
getProgramSearchPath = progSearchPath
-- | Change the current 'ProgramSearchPath' used by the 'ProgramDb'.
-- This will affect programs that are configured from here on, so you
-- should usually set it before configuring any programs.
--
setProgramSearchPath :: ProgramSearchPath -> ProgramDb -> ProgramDb
setProgramSearchPath searchpath db = db { progSearchPath = searchpath }
-- | Modify the current 'ProgramSearchPath' used by the 'ProgramDb'.
-- This will affect programs that are configured from here on, so you
-- should usually modify it before configuring any programs.
--
modifyProgramSearchPath :: (ProgramSearchPath -> ProgramSearchPath)
-> ProgramDb
-> ProgramDb
modifyProgramSearchPath f db =
setProgramSearchPath (f $ getProgramSearchPath db) db
-- |User-specify this path. Basically override any path information
-- for this program in the configuration. If it's not a known
-- program ignore it.
--
userSpecifyPath :: String -- ^Program name
-> FilePath -- ^user-specified path to the program
-> ProgramDb -> ProgramDb
userSpecifyPath name path = updateUnconfiguredProgs $
flip Map.update name $ \(prog, _, args) -> Just (prog, Just path, args)
userMaybeSpecifyPath :: String -> Maybe FilePath
-> ProgramDb -> ProgramDb
userMaybeSpecifyPath _ Nothing conf = conf
userMaybeSpecifyPath name (Just path) conf = userSpecifyPath name path conf
-- |User-specify the arguments for this program. Basically override
-- any args information for this program in the configuration. If it's
-- not a known program, ignore it..
userSpecifyArgs :: String -- ^Program name
-> [ProgArg] -- ^user-specified args
-> ProgramDb
-> ProgramDb
userSpecifyArgs name args' =
updateUnconfiguredProgs
(flip Map.update name $
\(prog, path, args) -> Just (prog, path, args ++ args'))
. updateConfiguredProgs
(flip Map.update name $
\prog -> Just prog { programOverrideArgs = programOverrideArgs prog
++ args' })
-- | Like 'userSpecifyPath' but for a list of progs and their paths.
--
userSpecifyPaths :: [(String, FilePath)]
-> ProgramDb
-> ProgramDb
userSpecifyPaths paths conf =
foldl' (\conf' (prog, path) -> userSpecifyPath prog path conf') conf paths
-- | Like 'userSpecifyPath' but for a list of progs and their args.
--
userSpecifyArgss :: [(String, [ProgArg])]
-> ProgramDb
-> ProgramDb
userSpecifyArgss argss conf =
foldl' (\conf' (prog, args) -> userSpecifyArgs prog args conf') conf argss
-- | Get the path that has been previously specified for a program, if any.
--
userSpecifiedPath :: Program -> ProgramDb -> Maybe FilePath
userSpecifiedPath prog =
join . fmap (\(_,p,_)->p) . Map.lookup (programName prog) . unconfiguredProgs
-- | Get any extra args that have been previously specified for a program.
--
userSpecifiedArgs :: Program -> ProgramDb -> [ProgArg]
userSpecifiedArgs prog =
maybe [] (\(_,_,as)->as) . Map.lookup (programName prog) . unconfiguredProgs
-- -----------------------------
-- Managing configured programs
-- | Try to find a configured program
lookupProgram :: Program -> ProgramDb -> Maybe ConfiguredProgram
lookupProgram prog = Map.lookup (programName prog) . configuredProgs
-- | Update a configured program in the database.
updateProgram :: ConfiguredProgram -> ProgramDb
-> ProgramDb
updateProgram prog = updateConfiguredProgs $
Map.insert (programId prog) prog
-- | List all configured programs.
configuredPrograms :: ProgramDb -> [ConfiguredProgram]
configuredPrograms = Map.elems . configuredProgs
-- ---------------------------
-- Configuring known programs
-- | Try to configure a specific program. If the program is already included in
-- the collection of unconfigured programs then we use any user-supplied
-- location and arguments. If the program gets configured successfully it gets
-- added to the configured collection.
--
-- Note that it is not a failure if the program cannot be configured. It's only
-- a failure if the user supplied a location and the program could not be found
-- at that location.
--
-- The reason for it not being a failure at this stage is that we don't know up
-- front all the programs we will need, so we try to configure them all.
-- To verify that a program was actually successfully configured use
-- 'requireProgram'.
--
configureProgram :: Verbosity
-> Program
-> ProgramDb
-> IO ProgramDb
configureProgram verbosity prog conf = do
let name = programName prog
maybeLocation <- case userSpecifiedPath prog conf of
Nothing -> programFindLocation prog verbosity (progSearchPath conf)
>>= return . fmap FoundOnSystem
Just path -> do
absolute <- doesExecutableExist path
if absolute
then return (Just (UserSpecified path))
else findProgramOnSearchPath verbosity (progSearchPath conf) path
>>= maybe (die notFound) (return . Just . UserSpecified)
where notFound = "Cannot find the program '" ++ name
++ "'. User-specified path '"
++ path ++ "' does not refer to an executable and "
++ "the program is not on the system path."
case maybeLocation of
Nothing -> return conf
Just location -> do
version <- programFindVersion prog verbosity (locationPath location)
newPath <- programSearchPathAsPATHVar (progSearchPath conf)
let configuredProg = ConfiguredProgram {
programId = name,
programVersion = version,
programDefaultArgs = [],
programOverrideArgs = userSpecifiedArgs prog conf,
programOverrideEnv = [("PATH", Just newPath)],
programProperties = Map.empty,
programLocation = location
}
configuredProg' <- programPostConf prog verbosity configuredProg
return (updateConfiguredProgs (Map.insert name configuredProg') conf)
-- | Configure a bunch of programs using 'configureProgram'. Just a 'foldM'.
--
configurePrograms :: Verbosity
-> [Program]
-> ProgramDb
-> IO ProgramDb
configurePrograms verbosity progs conf =
foldM (flip (configureProgram verbosity)) conf progs
-- | Try to configure all the known programs that have not yet been configured.
--
configureAllKnownPrograms :: Verbosity
-> ProgramDb
-> IO ProgramDb
configureAllKnownPrograms verbosity conf =
configurePrograms verbosity
[ prog | (prog,_,_) <- Map.elems notYetConfigured ] conf
where
notYetConfigured = unconfiguredProgs conf
`Map.difference` configuredProgs conf
-- | reconfigure a bunch of programs given new user-specified args. It takes
-- the same inputs as 'userSpecifyPath' and 'userSpecifyArgs' and for all progs
-- with a new path it calls 'configureProgram'.
--
reconfigurePrograms :: Verbosity
-> [(String, FilePath)]
-> [(String, [ProgArg])]
-> ProgramDb
-> IO ProgramDb
reconfigurePrograms verbosity paths argss conf = do
configurePrograms verbosity progs
. userSpecifyPaths paths
. userSpecifyArgss argss
$ conf
where
progs = catMaybes [ lookupKnownProgram name conf | (name,_) <- paths ]
-- | Check that a program is configured and available to be run.
--
-- It raises an exception if the program could not be configured, otherwise
-- it returns the configured program.
--
requireProgram :: Verbosity -> Program -> ProgramDb
-> IO (ConfiguredProgram, ProgramDb)
requireProgram verbosity prog conf = do
-- If it's not already been configured, try to configure it now
conf' <- case lookupProgram prog conf of
Nothing -> configureProgram verbosity prog conf
Just _ -> return conf
case lookupProgram prog conf' of
Nothing -> die notFound
Just configuredProg -> return (configuredProg, conf')
where notFound = "The program '" ++ programName prog
++ "' is required but it could not be found."
-- | Check that a program is configured and available to be run.
--
-- Additionally check that the program version number is suitable and return
-- it. For example you could require 'AnyVersion' or @'orLaterVersion'
-- ('Version' [1,0] [])@
--
-- It returns the configured program, its version number and a possibly updated
-- 'ProgramDb'. If the program could not be configured or the version is
-- unsuitable, it returns an error value.
--
lookupProgramVersion
:: Verbosity -> Program -> VersionRange -> ProgramDb
-> IO (Either String (ConfiguredProgram, Version, ProgramDb))
lookupProgramVersion verbosity prog range programDb = do
-- If it's not already been configured, try to configure it now
programDb' <- case lookupProgram prog programDb of
Nothing -> configureProgram verbosity prog programDb
Just _ -> return programDb
case lookupProgram prog programDb' of
Nothing -> return $! Left notFound
Just configuredProg@ConfiguredProgram { programLocation = location } ->
case programVersion configuredProg of
Just version
| withinRange version range ->
return $! Right (configuredProg, version ,programDb')
| otherwise ->
return $! Left (badVersion version location)
Nothing ->
return $! Left (noVersion location)
where notFound = "The program '"
++ programName prog ++ "'" ++ versionRequirement
++ " is required but it could not be found."
badVersion v l = "The program '"
++ programName prog ++ "'" ++ versionRequirement
++ " is required but the version found at "
++ locationPath l ++ " is version " ++ display v
noVersion l = "The program '"
++ programName prog ++ "'" ++ versionRequirement
++ " is required but the version of "
++ locationPath l ++ " could not be determined."
versionRequirement
| isAnyVersion range = ""
| otherwise = " version " ++ display range
-- | Like 'lookupProgramVersion', but raises an exception in case of error
-- instead of returning 'Left errMsg'.
--
requireProgramVersion :: Verbosity -> Program -> VersionRange
-> ProgramDb
-> IO (ConfiguredProgram, Version, ProgramDb)
requireProgramVersion verbosity prog range programDb =
join $ either die return <$>
lookupProgramVersion verbosity prog range programDb
| DavidAlphaFox/ghc | libraries/Cabal/Cabal/Distribution/Simple/Program/Db.hs | Haskell | bsd-3-clause | 17,834 |
<?xml version="1.0" encoding="UTF-8"?><!DOCTYPE helpset PUBLIC "-//Sun Microsystems Inc.//DTD JavaHelp HelpSet Version 2.0//EN" "http://java.sun.com/products/javahelp/helpset_2_0.dtd">
<helpset version="2.0" xml:lang="id-ID">
<title>DOM XSS Aktif Memindai Aturan | ZAP Ekstensi</title>
<maps>
<homeID>top</homeID>
<mapref location="map.jhm"/>
</maps>
<view>
<name>TOC</name>
<label>Isi</label>
<type>org.zaproxy.zap.extension.help.ZapTocView</type>
<data>toc.xml</data>
</view>
<view>
<name>Index</name>
<label>Indeks</label>
<type>javax.help.IndexView</type>
<data>index.xml</data>
</view>
<view>
<name>Search</name>
<label>Pencarian</label>
<type>javax.help.SearchView</type>
<data engine="com.sun.java.help.search.DefaultSearchEngine">
JavaHelpSearch
</data>
</view>
<view>
<name>Favorites</name>
<label>Favorit</label>
<type>javax.help.FavoritesView</type>
</view>
</helpset> | kingthorin/zap-extensions | addOns/domxss/src/main/javahelp/org/zaproxy/zap/extension/domxss/resources/help_id_ID/helpset_id_ID.hs | Haskell | apache-2.0 | 986 |
<?xml version="1.0" encoding="UTF-8"?><!DOCTYPE helpset PUBLIC "-//Sun Microsystems Inc.//DTD JavaHelp HelpSet Version 2.0//EN" "http://java.sun.com/products/javahelp/helpset_2_0.dtd">
<helpset version="2.0" xml:lang="sr-CS">
<title>Requester</title>
<maps>
<homeID>requester</homeID>
<mapref location="map.jhm"/>
</maps>
<view>
<name>TOC</name>
<label>Contents</label>
<type>org.zaproxy.zap.extension.help.ZapTocView</type>
<data>toc.xml</data>
</view>
<view>
<name>Index</name>
<label>Index</label>
<type>javax.help.IndexView</type>
<data>index.xml</data>
</view>
<view>
<name>Search</name>
<label>Search</label>
<type>javax.help.SearchView</type>
<data engine="com.sun.java.help.search.DefaultSearchEngine">
JavaHelpSearch
</data>
</view>
<view>
<name>Favorites</name>
<label>Favorites</label>
<type>javax.help.FavoritesView</type>
</view>
</helpset> | thc202/zap-extensions | addOns/requester/src/main/javahelp/help_sr_CS/helpset_sr_CS.hs | Haskell | apache-2.0 | 960 |
module SubstituteBaseStruct where
import Substitute
import Recursive
import HasBaseStruct
import BaseSyntax
substE = substE' r
substE' r s e0 =
case mapEI id (subst s) id (esubst s) id id e0 of
HsId (HsVar x) -> s x
HsInfixApp e1 (HsVar x) e2 -> s x `hsApp` e1 `hsApp` e2
HsLeftSection e (HsVar x) -> s x `hsApp` e
HsRightSection (HsVar x) e -> error "SubstituteBaseStruct.subst HsRightSection"
e -> r e
instance MapExp e ds => MapExp e (DI i e p ds t c tp) where mapExp = mapExpD
instance MapExp e ds => MapExp e (EI i e p ds t c) where mapExp = mapExpE
mapExpD f = mapDI id f id (mapExp f) id id id
mapExpE f = mapEI id f id (mapExp f) id id
instance MapExp e ds => MapExp e (HsMatchI i e p ds) where
mapExp f = mapMatchI id f id (mapExp f)
instance MapExp e ds => MapExp e (HsModuleI m i ds) where
mapExp = mapDecls . mapExp
| forste/haReFork | tools/base/transforms/SubstituteBaseStruct.hs | Haskell | bsd-3-clause | 877 |
import Map
import MapAsSet
main = do
let x = insert 0 "foo"
. delete 1
. insert 1 undefined
. insert (6 :: Int) "foo"
$ empty
print (member 1 x)
print (keysSet x)
print (toList x)
print x
| ghc-android/ghc | testsuite/tests/driver/sigof02/Double.hs | Haskell | bsd-3-clause | 249 |
{- arch-tag: Tests for GZip module
Copyright (C) 2004-2011 John Goerzen <[email protected]>
All rights reserved.
For license and copyright information, see the file LICENSE
-}
module GZiptest(tests) where
import Test.HUnit
import System.FileArchive.GZip
import System.FilePath
import Data.Compression.Inflate
import System.IO.Binary
import System.IO
import Data.Either.Utils
import Data.List
mf fn exp conf = TestLabel fn $ TestCase $
do c <- readBinaryFile $
joinPath ["testsrc", "gzfiles", fn]
assertEqual "" exp (conf c)
{-
import System.FileArchive.GZip
import System.IO
import Data.Either.Utils
main = do
c <- hGetContents stdin
let x = snd . forceEither . read_header $ c
putStr x
test_bunches =
let f fn exp conv = mf fn exp (conv . snd . forceEither . read_header)
f2 c = let fn = "t/z" ++ (show c) ++ ".gz" in
f fn c (length . inflate_string)
in
map f2 [0..1000]
-}
test_inflate =
let f fn exp conv = mf fn exp (conv . snd . forceEither . read_header) in
[
f "t1.gz" "Test 1" inflate_string
,f "t1.gz" 6 (length . inflate_string)
,f "t1.gz" ("Test 1",
"\x19\xf8\x27\x99\x06\x00\x00\x00") inflate_string_remainder
,f "empty.gz" "" inflate_string
--,f "zeros.gz" 10485760 (length . inflate_string)
-- BAD BAD ,f "zeros.gz" (replicate (10 * 1048576) '\0') inflate_string
-- This line tests Igloo's code:
--,f "zeros.gz" True (\x -> (replicate 10485760 '\0') == inflate_string x)
]
test_header =
let f fn exp = mf fn exp (fst . forceEither . read_header)
in
[
f "t1.gz" Header {method = 8, flags = 0, extra = Nothing,
filename = Nothing, comment = Nothing,
mtime = 1102111446, xfl = 2, os = 3}
,f "empty.gz" Header {method = 8, flags = 8, extra = Nothing,
filename = Just "empty",
comment = Nothing,
mtime = 1102127257, xfl = 0, os = 3}
]
test_gunzip =
let f fn exp = mf fn exp decompress
in
[
f "t1.gz" ("Test 1", Nothing)
,f "t1bad.gz" ("Test 1", Just CRCError)
,f "t2.gz" ("Test 1Test 2", Nothing)
-- The following tests my code
{-
,mf "zeros.gz" True (\x -> case decompress x of
(y, _) -> y == replicate 10485760 '\0'
)
-}
]
tests = TestList [TestLabel "inflate" (TestList test_inflate),
TestLabel "header" (TestList test_header),
-- TestLabel "bunches" (TestList test_bunches),
TestLabel "gunzip" (TestList test_gunzip)
]
| haskellbr/missingh | missingh-all/testsrc/GZiptest.hs | Haskell | mit | 2,896 |
module Sandbox (tryProblem) where
import Problems (problems, Problem(..), Test)
import System.Process
import System.Timeout
import System.IO
import Control.Monad (void)
import Control.Concurrent.Async
import Data.Unique
import System.Directory
import Data.List
import Data.Aeson hiding (json)
import Data.Text (pack)
data TestRes = TestRes { test :: Test
, testSucc :: Bool
, testOut :: String
} deriving (Show)
data Mark = Mark { markSucc :: Bool
, markTests :: [TestRes]
} deriving (Show)
instance ToJSON TestRes where
toJSON (TestRes t s o) = object [ pack "test" .= t
, pack "success" .= s
, pack "output" .= o ]
instance ToJSON Mark where
toJSON (Mark s t) = object [pack "success" .= s, pack "tests" .= t]
trim :: Char -> String -> String
trim v = x . x where x = reverse . dropWhile (\x -> x == v)
hGetContentsEager :: Handle -> IO String
hGetContentsEager h = do
readable <- hIsReadable h
end <- hIsEOF h
if readable && not end then do
x <- hGetLine h
y <- hGetContentsEager h
return . trim '\n' $ x ++ "\n" ++ y
else
return ""
stripError :: String -> String
stripError [] = ""
stripError e | "/mnt/" `isPrefixOf` e = stripError $ drop 5 e
| "<interactive>:" `isPrefixOf` e = stripError $ drop 19 e
| "<interactive>" `isPrefixOf` e = stripError $ drop 13 e
| "*** Exception" `isPrefixOf` e = stripError $ drop 4 e
stripError (x:xs) = case take 13 xs == "<interactive>" of
True -> [x]
False -> x : stripError xs
makeTestRes :: Test -> Bool -> String -> String -> TestRes
makeTestRes t s r e | length e > 0 = TestRes t s $ stripError e
| otherwise = TestRes t s r
runTest :: Int -> String -> Test -> IO TestRes
runTest to c t = do
unique <- newUnique
let code = 'a':(show $ hashUnique unique) -- docker requires letter initial
let dir = "/tmp/99haskell/" ++ code
createDirectoryIfMissing True dir
writeFile (dir ++ "/Main.hs") c
(Just hin, Just hout, Just herr, hproc) <-
createProcess
(proc "docker" [ "run"
, "--name=" ++ code
, "--interactive=true"
, "--volume=" ++ dir ++ ":/mnt"
, "haskell"
, "/bin/bash" ])
{ std_in = CreatePipe, std_out = CreatePipe, std_err = CreatePipe }
hPutStrLn hin "ghci -v0 /mnt/Main.hs"
hPutStrLn hin $ fst t
hClose hin
maybeOutput <- timeout (to * 1000000) (return =<< (hGetContentsEager hout))
let output = case maybeOutput of Nothing -> ""
Just a -> a
error <- case maybeOutput of Nothing -> return $ "99Haskell: Timeout Error\
\. Program did not exit after "
++ show to ++ " seconds."
Just _ -> hGetContentsEager herr
hClose hout
hClose herr
async $ do
readProcess "docker" ["rm", "-f", code] ""
removeDirectoryRecursive dir
return $ makeTestRes t (output == snd t) output error
tryProblem :: Int -> String -> IO Value
tryProblem i c = do
allTests <- mapConcurrently (runTest 5 c) (tests $ problems !! (i - 1))
return . toJSON $ Mark (all (==True) [testSucc x | x <- allTests]) allTests
| bramgg/99haskell | Sandbox.hs | Haskell | mit | 3,624 |
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE Strict #-}
module SmallGL.SelectorObject
( SelectorObject (..)
, initSelectorObject
, releaseSelectorObjectRes
, updateSelectorSizeIfNeeded
) where
import Numeric.DataFrame.IO
import Unsafe.Coerce (unsafeCoerce)
import SmallGL.Types
import JavaScript.WebGL
data SelectorObject = SelectorObject
{ selFrameBuf :: !WebGLFramebuffer
, selRenderBuf :: !WebGLRenderbuffer
, selTexture :: !WebGLTexture
, selUbyteView :: !(IODataFrame GLubyte '[4])
, selUintView :: !(IODataFrame GLuint '[])
, selFrameSize :: !(GLsizei, GLsizei)
}
initSelectorObject :: WebGLRenderingContext -> (GLsizei, GLsizei) -> IO SelectorObject
initSelectorObject gl selFrameSize@(width,height) = do
selFrameBuf <- createFramebuffer gl
bindFramebuffer gl gl_FRAMEBUFFER $ Just selFrameBuf
selTexture <- createTexture gl
bindTexture gl gl_TEXTURE_2D $ Just selTexture
texImage2D gl gl_TEXTURE_2D 0 gl_RGBA width height 0 gl_RGBA gl_UNSIGNED_BYTE Nothing
setTexParameters gl
framebufferTexture2D gl gl_FRAMEBUFFER gl_COLOR_ATTACHMENT0 gl_TEXTURE_2D selTexture 0
bindTexture gl gl_TEXTURE_2D Nothing
selRenderBuf <- createRenderbuffer gl
bindRenderbuffer gl gl_RENDERBUFFER $ Just selRenderBuf
renderbufferStorage gl gl_RENDERBUFFER gl_DEPTH_COMPONENT16 width height
framebufferRenderbuffer gl gl_FRAMEBUFFER gl_DEPTH_ATTACHMENT gl_RENDERBUFFER selRenderBuf
bindRenderbuffer gl gl_RENDERBUFFER Nothing
bindFramebuffer gl gl_FRAMEBUFFER Nothing
selUbyteView <- newDataFrame
selUintView <- arrayBuffer selUbyteView >>= viewWord32Array @'[] >>=
\(SomeIODataFrame d) -> return (unsafeCoerce d)
return SelectorObject {..}
releaseSelectorObjectRes :: WebGLRenderingContext -> SelectorObject -> IO ()
releaseSelectorObjectRes gl SelectorObject {..} = do
deleteRenderbuffer gl selRenderBuf
deleteTexture gl selTexture
deleteFramebuffer gl selFrameBuf
updateSelectorSizeIfNeeded :: WebGLRenderingContext -> (GLsizei, GLsizei)
-> SelectorObject -> IO SelectorObject
updateSelectorSizeIfNeeded gl (nw,nh) so@SelectorObject {..}
| (ow, oh) <- selFrameSize
, ow < nw || oh < nh
, width <- max ow nw
, height <- max oh nh
= do releaseSelectorObjectRes gl so
initSelectorObject gl (width, height)
updateSelectorSizeIfNeeded _ _ so = pure so
| achirkin/qua-view | src/SmallGL/SelectorObject.hs | Haskell | mit | 2,480 |
import Control.Monad
main = print (perms [0..9] !! 999999)
others _ [] = []
others xs (y:zs) = (y, xs ++ zs) : others (xs ++ [y]) zs
perms [] = [[]]
perms list = do
(x, yz) <- others [] list
zy <- perms yz
return (x : zy)
-- perms :: [a] -> [a] -> [[a]]
-- perms [] [] = [[]]
-- perms xs [y] = liftM (y:) $ perms [] xs
-- perms xs (y:zs) = (liftM (y:) $ perms xs zs) ++ perms (y:xs) zs
| nickspinale/euler | complete/024.hs | Haskell | mit | 402 |
{-# LANGUAGE FlexibleInstances, TypeSynonymInstances, OverlappingInstances #-}
module Path where
import Data.List
import ListUtil
type Path = String
class Pathy a where
pathOf :: a -> Path
instance Pathy Path where
pathOf path = path
samePath :: Pathy a => Pathy b => a -> b -> Bool
samePath a b = pathOf a == pathOf b
parentOf :: Pathy a => Pathy b => a -> b -> Bool
parentOf parent child = (pathOf parent) ++ "/" `elem` inits (pathOf child)
parent :: Pathy a => a -> Path
parent path = reverse $ (drop n) $ reverse $ pathOf path
where n = 1 + length (lastPathElement path)
subPath :: Pathy a => Pathy b => a -> b -> Path
subPath root sub = (pathOf root) ++ "/" ++ (pathOf sub)
lastPathElement :: Pathy a => a -> Path
lastPathElement path = last $ pathElements path
firstPathElement :: Pathy a => a -> Path
firstPathElement path = head $ pathElements path
pathElements :: Pathy a => a -> [String]
pathElements path = split '/' (pathOf path)
isAbsolutePath :: Pathy a => a -> Bool
isAbsolutePath path = (pathOf path) `startsWith` "/"
joinPaths :: [Path] -> Path
joinPaths [] = ""
joinPaths [a] = a
joinPaths (a:rest) = a ++ "/" ++ (joinPaths rest)
| raimohanska/oegysync | Path.hs | Haskell | mit | 1,182 |
{-# LANGUAGE OverloadedStrings #-}
import qualified SDL
import Control.Concurrent (threadDelay)
import Linear (V2(..), V4(..))
import Linear.Affine (Point(P))
import Control.Monad (unless)
import Foreign.C.Types
import Data.Foldable (traverse_)
import System.IO (hPutStrLn, stderr)
main :: IO ()
main = do
SDL.initialize [SDL.InitVideo]
window <- SDL.createWindow "Mirrors and lasers" $ SDL.defaultWindow { SDL.windowInitialSize = V2 576 511 }
renderer <- SDL.createRenderer window (-1) SDL.defaultRenderer
tileset <- SDL.loadBMP "data/tileset.bmp" >>= SDL.createTextureFromSurface renderer
SDL.showWindow window
mainLoop window renderer tileset
SDL.destroyTexture tileset
SDL.destroyRenderer renderer
SDL.destroyWindow window
SDL.quit
mainLoop :: SDL.Window -> SDL.Renderer -> SDL.Texture -> IO ()
mainLoop window renderer tileset = do
event <- SDL.waitEvent
let quit = SDL.eventPayload event == SDL.QuitEvent
let (cx, cy) = case SDL.eventPayload event of
SDL.MouseMotionEvent da -> let P (V2 x y) = SDL.mouseMotionEventPos da in (fromIntegral x, fromIntegral y)
otherwise -> (fromIntegral 0, fromIntegral 0)
let posx = fromIntegral cx `div` (tileSize+2)
let posy = fromIntegral cy `div` (tileSize+2)
debug $ "PosX: " ++ show posx ++ ", PoxY: " ++ show posy
SDL.rendererDrawColor renderer SDL.$= V4 0 0 0 0
SDL.clear renderer
drawGrid window renderer
SDL.copyEx
renderer
tileset
(Just $ SDL.Rectangle (P $ V2 (CInt $ 32) -- pos x
(CInt $ 0)) -- pos y
(V2 tileSize tileSize)) -- dimension
(Just $ SDL.Rectangle (P $ V2 (CInt $ posx * tileSize + posx * 2 + 1) -- pos x
(CInt $ posy * tileSize + posy * 2 + 1)) -- pos y
(V2 tileSize tileSize)) -- dimension
(CDouble 0)
Nothing
(V2 False False)
SDL.present renderer
unless quit $ mainLoop window renderer tileset
drawGrid :: SDL.Window -> SDL.Renderer -> IO ()
drawGrid window renderer = do
V2 width height <- SDL.get $ SDL.windowSize window
let drawVertical x = SDL.drawLine renderer (P $ V2 x 0) (P $ V2 x height)
let drawHorizontal y = SDL.drawLine renderer (P $ V2 0 y) (P $ V2 (width - sidebarSize) y)
SDL.rendererDrawColor renderer SDL.$= V4 100 100 100 255
traverse_ drawVertical [0,34..width - sidebarSize]
traverse_ drawHorizontal [0,34..height]
where
sidebarSize = 2 + (4 * (tileSize + 1))
debug :: String -> IO ()
debug = hPutStrLn stderr -- TODO: Seems to produce an error on windows
tileSize :: Num a => a
tileSize = fromIntegral 32
| nitrix/lasers | src/Main.hs | Haskell | mit | 2,783 |
-- | The recommended process for exporting plugins is to create a new module
-- that exports a single function currying the first three arguments to
-- 'Plugin'. The remaining argument, the Slack secret token, can be
-- supplied in a separate file exporting the list of installed commands for
-- Haskbot. This enables you to recreate a registry of installed tokens and
-- corresponding secret tokens in a separate file outside of version control.
--
-- A basic /Hello World/ plugin can be created via:
--
-- > {-# LANGUAGE OverloadedStrings #-}
-- >
-- > module MyPlugins.HelloWorld (register) where
-- >
-- > import Data.Text
-- > import Network.Haskbot.Plugin
-- > import Network.Haskbot.Types
-- >
-- > name :: Command
-- > name = setCommand "hello_world"
-- >
-- > helpText :: Text
-- > helpText = "Have Haskbot say _Hello, World!_ in your current channel."
-- >
-- > handler :: HandlerFn
-- > handler slashCom = return $ replySameChan slashCom "Hello, World!"
-- >
-- > register :: Text -> Plugin
-- > register = Plugin name helpText handler . setToken
--
-- To run the plugin, create a new Slack /slash command/ integration
-- corresponding to the command @\/hello_world@ that points to your Haskbot
-- server. Add the plugin's @register@ function to your Haskbot server's
-- plugin registry like detailed in "Network.Haskbot", giving it the Slack
-- integration's secret token as the remaining argument. Rebuild and run the
-- server. Typing @\/hello_word@ into any Slack channel should return a
-- Haskbot response of /Hello, world!/
module Haskbot.Plugin
(
-- * The Plugin type
Plugin (..)
, HandlerFn
-- * Common Slack replies
, replySameChan, replyAsDM
-- internal use only
, runPlugin
, isAuthorized
, selectFrom
) where
import Control.Monad.Reader (lift)
import Data.List (find)
import Data.Text (Text)
import Haskbot.Incoming (Incoming (Incoming), addToSendQueue)
import Haskbot.Internal.Environment (HaskbotM)
import Haskbot.SlashCommand (SlashCom (..), token)
import Haskbot.Types
-- | The type of function run by a plugin. It receives the full
-- "Network.Haskbot.SlashCommand" invoked and can optionally return a
-- "Network.Haskbot.Incoming" reply
type HandlerFn = SlashCom -> HaskbotM (Maybe Incoming)
data Plugin =
Plugin { plCommand :: {-# UNPACK #-} !Command
-- ^ The command that invokes this plugin
, plHelpText :: {-# UNPACK #-} !Text
-- ^ Help text displayed for this plugin via
-- "Network.Haskbot.Plugin.Help"
, plHandler :: !HandlerFn
-- ^ The function run when a 'Plugin' is invoked
, plToken :: {-# UNPACK #-} !Token
-- ^ The secret token corresponding with this plugin's /slash command/
-- Slack integration
}
-- | Send a Slack reply to the same channel as where the corresponding /slash
-- command/ was invoked, formatted according to
-- <https://api.slack.com/docs/formatting Slack>
replySameChan :: SlashCom -> Text -> Maybe Incoming
replySameChan sc = Just . Incoming (Channel $ channelName sc)
-- | Send a Slack reply as a DM to the user who invoked the /slash command/,
-- formatted according to <https://api.slack.com/docs/formatting Slack>
replyAsDM :: SlashCom -> Text -> Maybe Incoming
replyAsDM sc = Just . Incoming (DirectMsg $ userName sc)
-- internal functions
runPlugin :: Plugin -> SlashCom -> HaskbotM ()
runPlugin p slashCom = do
reply <- plHandler p slashCom
case reply of
Just r -> addToSendQueue r
_ -> return ()
isAuthorized :: Plugin -> SlashCom -> Bool
isAuthorized plugin slashCom = plToken plugin == token slashCom
selectFrom :: [Plugin] -> Command -> Maybe Plugin
selectFrom list com = find (\p -> plCommand p == com) list
| Jonplussed/haskbot-core | src/Haskbot/Plugin.hs | Haskell | mit | 3,764 |
module Unison.Util.TQueue where
import Unison.Prelude
import UnliftIO.STM hiding (TQueue)
import qualified Control.Concurrent.Async as Async
import qualified Data.Sequence as S
import Data.Sequence (Seq((:<|)), (|>))
data TQueue a = TQueue (TVar (Seq a)) (TVar Word64)
newIO :: MonadIO m => m (TQueue a)
newIO = TQueue <$> newTVarIO mempty <*> newTVarIO 0
size :: TQueue a -> STM Int
size (TQueue q _) = S.length <$> readTVar q
-- Waits for this queue to reach a size <= target.
-- Consumes no elements; it's expected there is some
-- other thread which is consuming elements from the queue.
awaitSize :: Int -> TQueue a -> STM ()
awaitSize target q = size q >>= \n ->
if n <= target then pure ()
else retrySTM
peek :: TQueue a -> STM a
peek (TQueue v _) = readTVar v >>= \case
a :<| _ -> pure a
_ -> retrySTM
dequeue :: TQueue a -> STM a
dequeue (TQueue v _) = readTVar v >>= \case
a :<| as -> writeTVar v as *> pure a
_ -> retrySTM
undequeue :: TQueue a -> a -> STM ()
undequeue (TQueue v _) a = readTVar v >>= \
as -> writeTVar v (a :<| as)
tryDequeue :: TQueue a -> STM (Maybe a)
tryDequeue (TQueue v _) = readTVar v >>= \case
a :<| as -> writeTVar v as *> pure (Just a)
_ -> pure Nothing
dequeueN :: TQueue a -> Int -> STM [a]
dequeueN (TQueue v _) n = readTVar v >>= \s ->
if length s >= n then writeTVar v (S.drop n s) $> toList (S.take n s)
else retrySTM
-- return the number of enqueues over the life of the queue
enqueueCount :: TQueue a -> STM Word64
enqueueCount (TQueue _ count) = readTVar count
flush :: TQueue a -> STM [a]
flush (TQueue v _) = do
s <- readTVar v
writeTVar v mempty
pure . toList $ s
enqueue :: TQueue a -> a -> STM ()
enqueue (TQueue v count) a = do
modifyTVar' v (|> a)
modifyTVar' count (+1)
raceIO :: MonadIO m => STM a -> STM b -> m (Either a b)
raceIO a b = liftIO do
aa <- Async.async $ atomically a
ab <- Async.async $ atomically b
Async.waitEitherCancel aa ab
-- take all elements up to but not including the first not satisfying cond
tryPeekWhile :: (a -> Bool) -> TQueue a -> STM [a]
tryPeekWhile cond (TQueue v _) = toList . S.takeWhileL cond <$> readTVar v
-- block until at least one element is enqueued not satisfying cond,
-- then return the prefix before that
takeWhile :: (a -> Bool) -> TQueue a -> STM [a]
takeWhile cond (TQueue v _) = readTVar v >>= \s -> let
(left, right) = S.spanl cond s in
if null right then retrySTM
else writeTVar v right $> toList left
peekWhile :: (a -> Bool) -> TQueue a -> STM [a]
peekWhile cond (TQueue v _) = readTVar v >>= \s -> let
(left, right) = S.spanl cond s in
if null right then retrySTM
else pure $ toList left
| unisonweb/platform | parser-typechecker/src/Unison/Util/TQueue.hs | Haskell | mit | 2,669 |
{-# LANGUAGE PatternSynonyms #-}
-- For HasCallStack compatibility
{-# LANGUAGE ImplicitParams, ConstraintKinds, KindSignatures #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module JSDOM.Generated.Crypto
(getRandomValues, getRandomValues_, getSubtle, getWebkitSubtle,
Crypto(..), gTypeCrypto)
where
import Prelude ((.), (==), (>>=), return, IO, Int, Float, Double, Bool(..), Maybe, maybe, fromIntegral, round, realToFrac, fmap, Show, Read, Eq, Ord, Maybe(..))
import qualified Prelude (error)
import Data.Typeable (Typeable)
import Data.Traversable (mapM)
import Language.Javascript.JSaddle (JSM(..), JSVal(..), JSString, strictEqual, toJSVal, valToStr, valToNumber, valToBool, js, jss, jsf, jsg, function, asyncFunction, new, array, jsUndefined, (!), (!!))
import Data.Int (Int64)
import Data.Word (Word, Word64)
import JSDOM.Types
import Control.Applicative ((<$>))
import Control.Monad (void)
import Control.Lens.Operators ((^.))
import JSDOM.EventTargetClosures (EventName, unsafeEventName, unsafeEventNameAsync)
import JSDOM.Enums
-- | <https://developer.mozilla.org/en-US/docs/Web/API/Crypto.getRandomValues Mozilla Crypto.getRandomValues documentation>
getRandomValues ::
(MonadDOM m, IsArrayBufferView array) =>
Crypto -> array -> m ArrayBufferView
getRandomValues self array
= liftDOM
((self ^. jsf "getRandomValues" [toJSVal array]) >>=
fromJSValUnchecked)
-- | <https://developer.mozilla.org/en-US/docs/Web/API/Crypto.getRandomValues Mozilla Crypto.getRandomValues documentation>
getRandomValues_ ::
(MonadDOM m, IsArrayBufferView array) => Crypto -> array -> m ()
getRandomValues_ self array
= liftDOM (void (self ^. jsf "getRandomValues" [toJSVal array]))
-- | <https://developer.mozilla.org/en-US/docs/Web/API/Crypto.subtle Mozilla Crypto.subtle documentation>
getSubtle :: (MonadDOM m) => Crypto -> m SubtleCrypto
getSubtle self
= liftDOM ((self ^. js "subtle") >>= fromJSValUnchecked)
-- | <https://developer.mozilla.org/en-US/docs/Web/API/Crypto.webkitSubtle Mozilla Crypto.webkitSubtle documentation>
getWebkitSubtle :: (MonadDOM m) => Crypto -> m WebKitSubtleCrypto
getWebkitSubtle self
= liftDOM ((self ^. js "webkitSubtle") >>= fromJSValUnchecked)
| ghcjs/jsaddle-dom | src/JSDOM/Generated/Crypto.hs | Haskell | mit | 2,276 |
{-# LANGUAGE PatternSynonyms, ForeignFunctionInterface, JavaScriptFFI #-}
module GHCJS.DOM.JSFFI.Generated.ScriptProfileNode
(js_children, children, js_getId, getId, js_getFunctionName,
getFunctionName, js_getUrl, getUrl, js_getLineNumber,
getLineNumber, js_getColumnNumber, getColumnNumber,
ScriptProfileNode, castToScriptProfileNode, gTypeScriptProfileNode)
where
import Prelude ((.), (==), (>>=), return, IO, Int, Float, Double, Bool(..), Maybe, maybe, fromIntegral, round, fmap, Show, Read, Eq, Ord)
import Data.Typeable (Typeable)
import GHCJS.Types (JSRef(..), JSString, castRef)
import GHCJS.Foreign (jsNull)
import GHCJS.Foreign.Callback (syncCallback, asyncCallback, syncCallback1, asyncCallback1, syncCallback2, asyncCallback2, OnBlocked(..))
import GHCJS.Marshal (ToJSRef(..), FromJSRef(..))
import GHCJS.Marshal.Pure (PToJSRef(..), PFromJSRef(..))
import Control.Monad.IO.Class (MonadIO(..))
import Data.Int (Int64)
import Data.Word (Word, Word64)
import GHCJS.DOM.Types
import Control.Applicative ((<$>))
import GHCJS.DOM.EventTargetClosures (EventName, unsafeEventName)
import GHCJS.DOM.Enums
foreign import javascript unsafe "$1[\"children\"]()" js_children
:: JSRef ScriptProfileNode -> IO (JSRef [Maybe ScriptProfileNode])
-- | <https://developer.mozilla.org/en-US/docs/Web/API/ScriptProfileNode.children Mozilla ScriptProfileNode.children documentation>
children ::
(MonadIO m) => ScriptProfileNode -> m [Maybe ScriptProfileNode]
children self
= liftIO
((js_children (unScriptProfileNode self)) >>= fromJSRefUnchecked)
foreign import javascript unsafe "$1[\"id\"]" js_getId ::
JSRef ScriptProfileNode -> IO Word
-- | <https://developer.mozilla.org/en-US/docs/Web/API/ScriptProfileNode.id Mozilla ScriptProfileNode.id documentation>
getId :: (MonadIO m) => ScriptProfileNode -> m Word
getId self = liftIO (js_getId (unScriptProfileNode self))
foreign import javascript unsafe "$1[\"functionName\"]"
js_getFunctionName :: JSRef ScriptProfileNode -> IO JSString
-- | <https://developer.mozilla.org/en-US/docs/Web/API/ScriptProfileNode.functionName Mozilla ScriptProfileNode.functionName documentation>
getFunctionName ::
(MonadIO m, FromJSString result) => ScriptProfileNode -> m result
getFunctionName self
= liftIO
(fromJSString <$> (js_getFunctionName (unScriptProfileNode self)))
foreign import javascript unsafe "$1[\"url\"]" js_getUrl ::
JSRef ScriptProfileNode -> IO JSString
-- | <https://developer.mozilla.org/en-US/docs/Web/API/ScriptProfileNode.url Mozilla ScriptProfileNode.url documentation>
getUrl ::
(MonadIO m, FromJSString result) => ScriptProfileNode -> m result
getUrl self
= liftIO (fromJSString <$> (js_getUrl (unScriptProfileNode self)))
foreign import javascript unsafe "$1[\"lineNumber\"]"
js_getLineNumber :: JSRef ScriptProfileNode -> IO Word
-- | <https://developer.mozilla.org/en-US/docs/Web/API/ScriptProfileNode.lineNumber Mozilla ScriptProfileNode.lineNumber documentation>
getLineNumber :: (MonadIO m) => ScriptProfileNode -> m Word
getLineNumber self
= liftIO (js_getLineNumber (unScriptProfileNode self))
foreign import javascript unsafe "$1[\"columnNumber\"]"
js_getColumnNumber :: JSRef ScriptProfileNode -> IO Word
-- | <https://developer.mozilla.org/en-US/docs/Web/API/ScriptProfileNode.columnNumber Mozilla ScriptProfileNode.columnNumber documentation>
getColumnNumber :: (MonadIO m) => ScriptProfileNode -> m Word
getColumnNumber self
= liftIO (js_getColumnNumber (unScriptProfileNode self)) | plow-technologies/ghcjs-dom | src/GHCJS/DOM/JSFFI/Generated/ScriptProfileNode.hs | Haskell | mit | 3,610 |
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TupleSections #-}
-- | http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-codedeploy-deploymentgroup-targetgroupinfo.html
module Stratosphere.ResourceProperties.CodeDeployDeploymentGroupTargetGroupInfo where
import Stratosphere.ResourceImports
-- | Full data type definition for CodeDeployDeploymentGroupTargetGroupInfo.
-- See 'codeDeployDeploymentGroupTargetGroupInfo' for a more convenient
-- constructor.
data CodeDeployDeploymentGroupTargetGroupInfo =
CodeDeployDeploymentGroupTargetGroupInfo
{ _codeDeployDeploymentGroupTargetGroupInfoName :: Maybe (Val Text)
} deriving (Show, Eq)
instance ToJSON CodeDeployDeploymentGroupTargetGroupInfo where
toJSON CodeDeployDeploymentGroupTargetGroupInfo{..} =
object $
catMaybes
[ fmap (("Name",) . toJSON) _codeDeployDeploymentGroupTargetGroupInfoName
]
-- | Constructor for 'CodeDeployDeploymentGroupTargetGroupInfo' containing
-- required fields as arguments.
codeDeployDeploymentGroupTargetGroupInfo
:: CodeDeployDeploymentGroupTargetGroupInfo
codeDeployDeploymentGroupTargetGroupInfo =
CodeDeployDeploymentGroupTargetGroupInfo
{ _codeDeployDeploymentGroupTargetGroupInfoName = Nothing
}
-- | http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-codedeploy-deploymentgroup-targetgroupinfo.html#cfn-codedeploy-deploymentgroup-targetgroupinfo-name
cddgtgiName :: Lens' CodeDeployDeploymentGroupTargetGroupInfo (Maybe (Val Text))
cddgtgiName = lens _codeDeployDeploymentGroupTargetGroupInfoName (\s a -> s { _codeDeployDeploymentGroupTargetGroupInfoName = a })
| frontrowed/stratosphere | library-gen/Stratosphere/ResourceProperties/CodeDeployDeploymentGroupTargetGroupInfo.hs | Haskell | mit | 1,707 |
{-# LANGUAGE ExistentialQuantification #-}
module Light.Camera
( Camera(..), CameraBox, cameraBox
)
where
import Light.Film
import Light.Geometry
class Camera a where
cameraTransform :: a -> Transform
cameraFilm :: a -> Film
cameraRay :: a -> (Double, Double) -> Ray
data CameraBox = forall c. (Camera c, Transformable c, Show c) => CameraBox c
cameraBox :: (Camera c, Transformable c, Show c) => c -> CameraBox
cameraBox = CameraBox
instance Show CameraBox where
show (CameraBox c) = show c
instance Camera CameraBox where
cameraTransform (CameraBox c) = cameraTransform c
cameraFilm (CameraBox c) = cameraFilm c
cameraRay (CameraBox c) = cameraRay c
instance Transformable CameraBox where
transform t' (CameraBox c) = CameraBox (transform t' c)
| jtdubs/Light | src/Light/Camera.hs | Haskell | mit | 786 |
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TupleSections #-}
-- | http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-codebuild-project-projectcache.html
module Stratosphere.ResourceProperties.CodeBuildProjectProjectCache where
import Stratosphere.ResourceImports
-- | Full data type definition for CodeBuildProjectProjectCache. See
-- 'codeBuildProjectProjectCache' for a more convenient constructor.
data CodeBuildProjectProjectCache =
CodeBuildProjectProjectCache
{ _codeBuildProjectProjectCacheLocation :: Maybe (Val Text)
, _codeBuildProjectProjectCacheModes :: Maybe (ValList Text)
, _codeBuildProjectProjectCacheType :: Val Text
} deriving (Show, Eq)
instance ToJSON CodeBuildProjectProjectCache where
toJSON CodeBuildProjectProjectCache{..} =
object $
catMaybes
[ fmap (("Location",) . toJSON) _codeBuildProjectProjectCacheLocation
, fmap (("Modes",) . toJSON) _codeBuildProjectProjectCacheModes
, (Just . ("Type",) . toJSON) _codeBuildProjectProjectCacheType
]
-- | Constructor for 'CodeBuildProjectProjectCache' containing required fields
-- as arguments.
codeBuildProjectProjectCache
:: Val Text -- ^ 'cbppcType'
-> CodeBuildProjectProjectCache
codeBuildProjectProjectCache typearg =
CodeBuildProjectProjectCache
{ _codeBuildProjectProjectCacheLocation = Nothing
, _codeBuildProjectProjectCacheModes = Nothing
, _codeBuildProjectProjectCacheType = typearg
}
-- | http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-codebuild-project-projectcache.html#cfn-codebuild-project-projectcache-location
cbppcLocation :: Lens' CodeBuildProjectProjectCache (Maybe (Val Text))
cbppcLocation = lens _codeBuildProjectProjectCacheLocation (\s a -> s { _codeBuildProjectProjectCacheLocation = a })
-- | http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-codebuild-project-projectcache.html#cfn-codebuild-project-projectcache-modes
cbppcModes :: Lens' CodeBuildProjectProjectCache (Maybe (ValList Text))
cbppcModes = lens _codeBuildProjectProjectCacheModes (\s a -> s { _codeBuildProjectProjectCacheModes = a })
-- | http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-codebuild-project-projectcache.html#cfn-codebuild-project-projectcache-type
cbppcType :: Lens' CodeBuildProjectProjectCache (Val Text)
cbppcType = lens _codeBuildProjectProjectCacheType (\s a -> s { _codeBuildProjectProjectCacheType = a })
| frontrowed/stratosphere | library-gen/Stratosphere/ResourceProperties/CodeBuildProjectProjectCache.hs | Haskell | mit | 2,531 |
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE CPP #-}
module Hpack.Run (
run
, renderPackage
, RenderSettings(..)
, Alignment(..)
, CommaStyle(..)
, defaultRenderSettings
#ifdef TEST
, renderConditional
, renderFlag
, renderSourceRepository
, formatDescription
#endif
) where
import Prelude ()
import Prelude.Compat
import Control.Monad
import Data.Char
import Data.Maybe
import Data.List.Compat
import System.Exit.Compat
import System.FilePath
import Hpack.Util
import Hpack.Config
import Hpack.Render
import Hpack.FormattingHints
run :: FilePath -> IO ([String], FilePath, String)
run dir = do
mPackage <- readPackageConfig (dir </> packageConfig)
case mPackage of
Right (warnings, pkg) -> do
let cabalFile = dir </> (packageName pkg ++ ".cabal")
old <- tryReadFile cabalFile
let
FormattingHints{..} = sniffFormattingHints (fromMaybe "" old)
alignment = fromMaybe 16 formattingHintsAlignment
settings = formattingHintsRenderSettings
output = renderPackage settings alignment formattingHintsFieldOrder formattingHintsSectionsFieldOrder pkg
return (warnings, cabalFile, output)
Left err -> die err
renderPackage :: RenderSettings -> Alignment -> [String] -> [(String, [String])] -> Package -> String
renderPackage settings alignment existingFieldOrder sectionsFieldOrder Package{..} = intercalate "\n" (unlines header : chunks)
where
chunks :: [String]
chunks = map unlines . filter (not . null) . map (render settings 0) $ sortSectionFields sectionsFieldOrder stanzas
header :: [String]
header = concatMap (render settings {renderSettingsFieldAlignment = alignment} 0) fields
extraSourceFiles :: Element
extraSourceFiles = Field "extra-source-files" (LineSeparatedList packageExtraSourceFiles)
dataFiles :: Element
dataFiles = Field "data-files" (LineSeparatedList packageDataFiles)
sourceRepository = maybe [] (return . renderSourceRepository) packageSourceRepository
library = maybe [] (return . renderLibrary) packageLibrary
stanzas :: [Element]
stanzas =
extraSourceFiles
: dataFiles
: sourceRepository
++ concat [
map renderFlag packageFlags
, library
, renderExecutables packageExecutables
, renderTests packageTests
, renderBenchmarks packageBenchmarks
]
fields :: [Element]
fields = sortFieldsBy existingFieldOrder . mapMaybe (\(name, value) -> Field name . Literal <$> value) $ [
("name", Just packageName)
, ("version", Just packageVersion)
, ("synopsis", packageSynopsis)
, ("description", (formatDescription alignment <$> packageDescription))
, ("category", packageCategory)
, ("stability", packageStability)
, ("homepage", packageHomepage)
, ("bug-reports", packageBugReports)
, ("author", formatList packageAuthor)
, ("maintainer", formatList packageMaintainer)
, ("copyright", formatList packageCopyright)
, ("license", packageLicense)
, ("license-file", packageLicenseFile)
, ("tested-with", packageTestedWith)
, ("build-type", Just "Simple")
, ("cabal-version", cabalVersion)
]
formatList :: [String] -> Maybe String
formatList xs = guard (not $ null xs) >> (Just $ intercalate separator xs)
where
separator = let Alignment n = alignment in ",\n" ++ replicate n ' '
cabalVersion :: Maybe String
cabalVersion = maximum [
Just ">= 1.10"
, packageLibrary >>= libCabalVersion
]
where
libCabalVersion :: Section Library -> Maybe String
libCabalVersion sect = ">= 1.21" <$ guard (hasReexportedModules sect)
hasReexportedModules :: Section Library -> Bool
hasReexportedModules = not . null . libraryReexportedModules . sectionData
sortSectionFields :: [(String, [String])] -> [Element] -> [Element]
sortSectionFields sectionsFieldOrder = go
where
go sections = case sections of
[] -> []
Stanza name fields : xs | Just fieldOrder <- lookup name sectionsFieldOrder -> Stanza name (sortFieldsBy fieldOrder fields) : go xs
x : xs -> x : go xs
formatDescription :: Alignment -> String -> String
formatDescription (Alignment alignment) description = case map emptyLineToDot $ lines description of
x : xs -> intercalate "\n" (x : map (indentation ++) xs)
[] -> ""
where
n = max alignment (length ("description: " :: String))
indentation = replicate n ' '
emptyLineToDot xs
| isEmptyLine xs = "."
| otherwise = xs
isEmptyLine = all isSpace
renderSourceRepository :: SourceRepository -> Element
renderSourceRepository SourceRepository{..} = Stanza "source-repository head" [
Field "type" "git"
, Field "location" (Literal sourceRepositoryUrl)
, Field "subdir" (maybe "" Literal sourceRepositorySubdir)
]
renderFlag :: Flag -> Element
renderFlag Flag {..} = Stanza ("flag " ++ flagName) $ description ++ [
Field "manual" (Literal $ show flagManual)
, Field "default" (Literal $ show flagDefault)
]
where
description = maybe [] (return . Field "description" . Literal) flagDescription
renderExecutables :: [Section Executable] -> [Element]
renderExecutables = map renderExecutable
renderExecutable :: Section Executable -> Element
renderExecutable sect@(sectionData -> Executable{..}) =
Stanza ("executable " ++ executableName) (renderExecutableSection sect)
renderTests :: [Section Executable] -> [Element]
renderTests = map renderTest
renderTest :: Section Executable -> Element
renderTest sect@(sectionData -> Executable{..}) =
Stanza ("test-suite " ++ executableName)
(Field "type" "exitcode-stdio-1.0" : renderExecutableSection sect)
renderBenchmarks :: [Section Executable] -> [Element]
renderBenchmarks = map renderBenchmark
renderBenchmark :: Section Executable -> Element
renderBenchmark sect@(sectionData -> Executable{..}) =
Stanza ("benchmark " ++ executableName)
(Field "type" "exitcode-stdio-1.0" : renderExecutableSection sect)
renderExecutableSection :: Section Executable -> [Element]
renderExecutableSection sect@(sectionData -> Executable{..}) =
mainIs : renderSection sect ++ [otherModules, defaultLanguage]
where
mainIs = Field "main-is" (Literal executableMain)
otherModules = renderOtherModules executableOtherModules
renderLibrary :: Section Library -> Element
renderLibrary sect@(sectionData -> Library{..}) = Stanza "library" $
renderSection sect ++
maybe [] (return . renderExposed) libraryExposed ++ [
renderExposedModules libraryExposedModules
, renderOtherModules libraryOtherModules
, renderReexportedModules libraryReexportedModules
, defaultLanguage
]
renderExposed :: Bool -> Element
renderExposed = Field "exposed" . Literal . show
renderSection :: Section a -> [Element]
renderSection Section{..} = [
renderSourceDirs sectionSourceDirs
, renderDefaultExtensions sectionDefaultExtensions
, renderOtherExtensions sectionOtherExtensions
, renderGhcOptions sectionGhcOptions
, renderGhcProfOptions sectionGhcProfOptions
, renderCppOptions sectionCppOptions
, renderCCOptions sectionCCOptions
, Field "include-dirs" (LineSeparatedList sectionIncludeDirs)
, Field "install-includes" (LineSeparatedList sectionInstallIncludes)
, Field "c-sources" (LineSeparatedList sectionCSources)
, Field "extra-lib-dirs" (LineSeparatedList sectionExtraLibDirs)
, Field "extra-libraries" (LineSeparatedList sectionExtraLibraries)
, renderLdOptions sectionLdOptions
, renderDependencies sectionDependencies
, renderBuildTools sectionBuildTools
]
++ maybe [] (return . renderBuildable) sectionBuildable
++ map renderConditional sectionConditionals
renderConditional :: Conditional -> Element
renderConditional (Conditional condition sect mElse) = case mElse of
Nothing -> if_
Just else_ -> Group if_ (Stanza "else" $ renderSection else_)
where
if_ = Stanza ("if " ++ condition) (renderSection sect)
defaultLanguage :: Element
defaultLanguage = Field "default-language" "Haskell2010"
renderSourceDirs :: [String] -> Element
renderSourceDirs = Field "hs-source-dirs" . CommaSeparatedList
renderExposedModules :: [String] -> Element
renderExposedModules = Field "exposed-modules" . LineSeparatedList
renderOtherModules :: [String] -> Element
renderOtherModules = Field "other-modules" . LineSeparatedList
renderReexportedModules :: [String] -> Element
renderReexportedModules = Field "reexported-modules" . LineSeparatedList
renderDependencies :: [Dependency] -> Element
renderDependencies = Field "build-depends" . CommaSeparatedList . map dependencyName
renderGhcOptions :: [GhcOption] -> Element
renderGhcOptions = Field "ghc-options" . WordList
renderGhcProfOptions :: [GhcProfOption] -> Element
renderGhcProfOptions = Field "ghc-prof-options" . WordList
renderCppOptions :: [CppOption] -> Element
renderCppOptions = Field "cpp-options" . WordList
renderCCOptions :: [CCOption] -> Element
renderCCOptions = Field "cc-options" . WordList
renderLdOptions :: [LdOption] -> Element
renderLdOptions = Field "ld-options" . WordList
renderBuildable :: Bool -> Element
renderBuildable = Field "buildable" . Literal . show
renderDefaultExtensions :: [String] -> Element
renderDefaultExtensions = Field "default-extensions" . WordList
renderOtherExtensions :: [String] -> Element
renderOtherExtensions = Field "other-extensions" . WordList
renderBuildTools :: [Dependency] -> Element
renderBuildTools = Field "build-tools" . CommaSeparatedList . map dependencyName
| yamadapc/hpack-convert | src/Hpack/Run.hs | Haskell | mit | 9,779 |
module CAH.Cards.Import where
import CAH.Cards.Types
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.IO as T
import qualified Data.ByteString.Lazy as BS
import Data.Aeson
import Data.Set (Set)
import qualified Data.Set as S
import System.IO
import Control.Monad
import Control.Applicative
instance FromJSON WhiteCard where
parseJSON (Object v) = do
(x :: Text) <- v .: "type"
guard (x == "Answer")
WhiteCard <$> v .: "value"
parseJSON _ = mzero
instance FromJSON BlackCard where
parseJSON (Object v) = do
(x :: Text) <- v .: "type"
guard (x == "Question")
BlackCard . convertT <$> v .: "value"
parseJSON _ = mzero
-- naive function
convertT :: String -> [HText]
convertT xs =
let v = go id xs
in if countHoles (BlackCard v) == 0
then v ++ [Txt " ", InvisibleHole]
else v
where go dlist ('%':'s':xs) = Txt (T.pack (dlist [])) : VisibleHole : go id xs
go dlist ('%':'%':xs) = go (dlist . ('%':)) xs
go dlist (x:xs) = go (dlist . (x:)) xs
go dlist [] = [Txt (T.pack (dlist []))]
parseCards :: (Ord a, FromJSON a) => FilePath -> IO (Maybe (Set a))
parseCards = fmap decode . BS.readFile
| EXio4/ircah | src/CAH/Cards/Import.hs | Haskell | mit | 1,430 |
import Data.List.Split
import Data.Char
import Control.Arrow
palindromeMoveCnt :: String -> Int
palindromeMoveCnt s = sum diffs
where [start, restM1] = (chunksOf $ (length s + 1) `div` 2) s
rest = if length s `mod` 2 /= 0 then last start : restM1 else restM1
f a b = abs $ ord b - ord a
diffs = zipWith f start (reverse rest)
main :: IO ()
main = do
_ <- getLine
interact $ lines >>> map (palindromeMoveCnt >>> show) >>> unlines | Dobiasd/HackerRank-solutions | Algorithms/Warmup/The_Love-Letter_Mystery/Main.hs | Haskell | mit | 460 |
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TupleSections #-}
-- | http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-ec2-ebs-volumeattachment.html
module Stratosphere.Resources.EC2VolumeAttachment where
import Stratosphere.ResourceImports
-- | Full data type definition for EC2VolumeAttachment. See
-- 'ec2VolumeAttachment' for a more convenient constructor.
data EC2VolumeAttachment =
EC2VolumeAttachment
{ _eC2VolumeAttachmentDevice :: Val Text
, _eC2VolumeAttachmentInstanceId :: Val Text
, _eC2VolumeAttachmentVolumeId :: Val Text
} deriving (Show, Eq)
instance ToResourceProperties EC2VolumeAttachment where
toResourceProperties EC2VolumeAttachment{..} =
ResourceProperties
{ resourcePropertiesType = "AWS::EC2::VolumeAttachment"
, resourcePropertiesProperties =
hashMapFromList $ catMaybes
[ (Just . ("Device",) . toJSON) _eC2VolumeAttachmentDevice
, (Just . ("InstanceId",) . toJSON) _eC2VolumeAttachmentInstanceId
, (Just . ("VolumeId",) . toJSON) _eC2VolumeAttachmentVolumeId
]
}
-- | Constructor for 'EC2VolumeAttachment' containing required fields as
-- arguments.
ec2VolumeAttachment
:: Val Text -- ^ 'ecvaDevice'
-> Val Text -- ^ 'ecvaInstanceId'
-> Val Text -- ^ 'ecvaVolumeId'
-> EC2VolumeAttachment
ec2VolumeAttachment devicearg instanceIdarg volumeIdarg =
EC2VolumeAttachment
{ _eC2VolumeAttachmentDevice = devicearg
, _eC2VolumeAttachmentInstanceId = instanceIdarg
, _eC2VolumeAttachmentVolumeId = volumeIdarg
}
-- | http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-ec2-ebs-volumeattachment.html#cfn-ec2-ebs-volumeattachment-device
ecvaDevice :: Lens' EC2VolumeAttachment (Val Text)
ecvaDevice = lens _eC2VolumeAttachmentDevice (\s a -> s { _eC2VolumeAttachmentDevice = a })
-- | http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-ec2-ebs-volumeattachment.html#cfn-ec2-ebs-volumeattachment-instanceid
ecvaInstanceId :: Lens' EC2VolumeAttachment (Val Text)
ecvaInstanceId = lens _eC2VolumeAttachmentInstanceId (\s a -> s { _eC2VolumeAttachmentInstanceId = a })
-- | http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-ec2-ebs-volumeattachment.html#cfn-ec2-ebs-volumeattachment-volumeid
ecvaVolumeId :: Lens' EC2VolumeAttachment (Val Text)
ecvaVolumeId = lens _eC2VolumeAttachmentVolumeId (\s a -> s { _eC2VolumeAttachmentVolumeId = a })
| frontrowed/stratosphere | library-gen/Stratosphere/Resources/EC2VolumeAttachment.hs | Haskell | mit | 2,521 |
{- Copyright 2014 David Farrell <[email protected]>
- Licensed under the Apache License, Version 2.0 (the "License");
- you may not use this file except in compliance with the License.
- You may obtain a copy of the License at
- http://www.apache.org/licenses/LICENSE-2.0
- Unless required by applicable law or agreed to in writing, software
- distributed under the License is distributed on an "AS IS" BASIS,
- WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
- See the License for the specific language governing permissions and
- limitations under the License.
-}
module Whois where
import Data.Char (toUpper)
import qualified Data.Map as M
import qualified Data.IntMap as IM
import Control.Monad (unless)
import IRC.Message
import IRC.Numeric
import IRC.Action
import qualified IRC.Server.Client as Client
import IRC.Server.Environment (whenRegistered)
import qualified IRC.Server.Environment as Env
import Config
import Plugin
plugin = defaultPlugin {handlers=[CommandHandler "WHOIS" whois]}
whois :: CommandHSpec
{-
whois env (Message _ _ (server:_:_))
| isClientRegistered client = do
sendNumeric env numERR_NOSUCHSERVER [server, "No such server"]
return env
| otherwise = return env
where client = Env.client env
-}
whois env (Message pfx cmd (_:target:_)) = whois env (Message pfx cmd [target])
whois env (Message _ _ (target:[])) = whenRegistered env $ do
if M.member targetUpper (Env.uids local)
then do
let targetClient = Env.clients local IM.! (Env.uids local M.! targetUpper)
Just nick = Client.nick targetClient
Just user = Client.user targetClient
Just host = Client.host targetClient
Just real = Client.realName targetClient
channels = Client.channels targetClient
as =
[ NamedAction "WhoisUser" $ \e -> sendNumeric e numRPL_WHOISUSER [nick, user, host, "*", real]
>> return e
, NamedAction "WhoisChans" $ \e -> unless (null channels)
(sendNumeric e numRPL_WHOISCHANNELS [nick, unwords channels]) >> return e
, NamedAction "WhoisServer" $ \e -> sendNumeric e numRPL_WHOISSERVER [nick, serverName, serverDesc]
>> return e
, GenericAction $ \e -> sendNumeric e numRPL_ENDOFWHOIS [nick, "End of /WHOIS list"] >> return e
]
env {Env.actions=as++Env.actions env}
else do
let a = GenericAction $ \e -> sendNumeric e numERR_NOSUCHNICK [target, "No such nick"] >> return e
env {Env.actions=a:Env.actions env}
where
cp = Env.config env
serverName = getConfigString cp "info" "name"
serverDesc = getConfigString cp "info" "description"
targetUpper = map toUpper target
local = Env.local env
whois env _ = whenRegistered env $ env {Env.actions=a:Env.actions env}
where a = GenericAction $ \e -> sendNumeric e numERR_NEEDMOREPARAMS ["WHOIS", "Not enough parameters"]
>> return e
| shockkolate/lambdircd | plugins.old/Whois.hs | Haskell | apache-2.0 | 3,121 |
-- Copyright (c) 2013, Finn Espen Gundersen
-- All rights reserved
-- Licensed under the 2-clause Simplified BSD (FreeBSD) License
-- | Pure module for encoding and decoding Google Polyline format as specified in
-- https://developers.google.com/maps/documentation/utilities/polylinealgorithm
module GPolyline (encodeline,encodeunsigned,decodeline,decodeunsigned) where
import Data.Word
import Data.Bits
import Data.Char
import Data.List.Split
type Point = (Double,Double)
example_decoded = [(38.5, -120.2), (40.7, -120.95), (43.252, -126.453)]
example_encoded = "_p~iF~ps|U_ulLnnqC_mqNvxq`@"
example_encoded2 = "ctteJe{{b@EESCKWAWCMAEGSQQ]Yo@"
example_decoded2 = [(58.765620000000006,5.88227),(58.76565000000001,5.8823),(58.76575000000001,5.88232),(58.76581000000001,5.88244),(58.76582000000001,5.88256),(58.76584000000001,5.88263),(58.765850000000015,5.88266),(58.76589000000001,5.882759999999999),(58.76598000000001,5.8828499999999995),(58.76613000000001,5.88298),(58.76637000000001,5.88298)]
example_encoded3 = "ctteJe{{b@E?E?SCK?WAWCMAEGSQQ]Yo@"
encodeline :: [Point] -> String
encodeline points = concatMap encodepoint rels
where rels = transform points calcoffsets -- step1 turn into offsets from first point
encodepoint (latoff,lngoff) = encodefloat latoff ++ encodefloat lngoff
decodeline :: String -> [Point]
decodeline str = transform points calcoffsets'
where chunks = chunkinput $ prepareinput str
floats = map (decodefloat) chunks
points = pairup floats
decodeunsigned :: String -> Int -- convenience function when we know that a string has only one unsigned
decodeunsigned str = fromIntegral $ createvalue 5 (clrthem (prepareinput str))
encodeunsigned :: Int -> String -- convenience function when we have just an unsigned
encodeunsigned off =
map (\b -> chr (fromIntegral(b+63))) w32l
where w32l = shorten $ thedrop (chunkvalue 5 (fromIntegral off))
shorten wrd
| null wrd = [0]
| otherwise = orthem $ reverse wrd
thedrop wrd = dropWhile (==0) (reverse wrd) -- remove unnecessary blocks (part of step 6)
-- turns list of values into list of pairs
-- map (\[a,b] -> (a.b)) (chunksOf 2 <list>) is more succinct, but fails on odd-length
pairup :: [a] -> [(a,a)]
pairup [] = []
pairup (x:[]) = [] -- throw away odd element if any (should not appear in well-formed string)
pairup (x:y:xs) = (x,y) : pairup xs
-- Converts a list of relative vectors to list of absolute points and vice versa
transform :: [Point] -> (Point -> [Point] -> [Point]) -> [Point]
transform [] _ = []
transform (x:xs) transformer
| null xs = [x]
| otherwise = x : transformer x xs
-- Used to convert a list of absolute points to list of relative vectors
calcoffsets :: Point -> [Point] -> [Point]
calcoffsets _ [] = []
calcoffsets (xprev,yprev) lst =
(x-xprev,y-yprev) : calcoffsets (x,y) (tail lst)
where (x,y) = head lst
-- Used to convert a list of relative vectors to list of absolute points
calcoffsets' :: Point -> [Point] -> [Point]
calcoffsets' _ [] = []
calcoffsets' (xprev,yprev) lst =
(x+xprev,y+yprev) : calcoffsets' (x+xprev,y+yprev) (tail lst)
where (x,y) = head lst
encodefloat :: Double -> String -- steps 9,10,11: add 63 and convert to ascii
encodefloat off =
map (\b -> chr (fromIntegral(b+63))) w32l
where w32l = shorten $ thedrop (chunkvalue 5 (preparefloat off))
shorten wrd
| null wrd = [0]
| otherwise = orthem $ reverse wrd
thedrop wrd = dropWhile (==0) (reverse wrd) -- remove unnecessary blocks (part of step 6)
decodefloat :: [Word32] -> Double
decodefloat lst = 0.00001 * res
where val = createvalue 5 (clrthem lst)
num = shiftR val 1
res
| testBit val 0 = -fromIntegral (num+1)
| otherwise = fromIntegral num
orthem :: [Word32] -> [Word32] -- step8 bitwise or all blocks except last with 0x20
orthem [] = []
orthem (x:[]) = [x]
orthem (x:xs) = (x .|. 32) : orthem xs
clrthem :: [Word32] -> [Word32] -- reverse of step8
clrthem [] = []
clrthem (x:[]) = [x]
clrthem (x:xs) = (clearBit x 5) : clrthem xs
chunkvalue :: Int -> Word32 -> [Word32] -- step6+7 break into 5bit chunks and reverse
chunkvalue bitspersegment wrd =
[(shiftR wrd b) .&. mask | b <- [0,bitspersegment..maxbits]]
where mask = (bit bitspersegment) - 1
maxbits = 25 -- should be 31 in general, but always max 25 for GPolyline
createvalue :: Int -> [Word32] -> Word32 -- reverse of step6+7, put reverse list of chunks together to one value
createvalue bitspersegment chunks =
sum $ zipWith (*) chunks [mul^e | e <- [0..]]
where mul = bit bitspersegment :: Word32
-- First steps, turning double into word32 (with max 25 bits + 1bit pos/neg content)
preparefloat :: Double -> Word32
preparefloat val = bin3
where int = round (val * 100000) -- step2 multiply by 1e5 and round
bin = fromIntegral int :: Word32 -- step3 convert to binary (2's complement for negs)
bin2 = shiftL bin 1 -- step4 left shift
bin3 -- step5 complement if negative
| int < 0 = complement bin2
| otherwise = bin2
chunkinput :: [Word32] -> [[Word32]]
chunkinput vals = splt (\v -> not $ testBit v 5) vals
where splt = split . keepDelimsR . whenElt
prepareinput :: String -> [Word32]
prepareinput str = map fromIntegral vals
where vals = map (\c -> (-63) + ord c) str
| fegu/gpolyline | GPolyline.hs | Haskell | bsd-2-clause | 5,497 |
{-| An implementation of the queue from
<http://zookeeper.apache.org/doc/trunk/recipes.html#sc_recipes_Queues>.
The queue node will be automatically created and removed as necessary, and must
not be used for any other purposes. The parent node of the queue node must
already exist.
Queues may contain both non-ephemeral and ephemeral values.
-}
module Zookeeper.Queue ( push, pushEphemeral, pop, popNonBlocking ) where
import Control.Concurrent.MVar ( newMVar, putMVar, takeMVar )
import Control.Exception as E ( catch, try )
import Control.Monad ( liftM )
import Data.List ( sort )
import System.FilePath.Posix ( (</>) )
import qualified Zookeeper.Core as C
push_ :: Bool -> C.Handle -> String -> String -> IO ()
push_ isEphemeral handle path value = do
-- Create the parent node to store the child nodes in. If the parent node already exists then
-- this will cause a NodeExists exception; we catch (and ignore) this exception.
(C.create handle path "" [] C.openAclUnsafe >> return ()) `E.catch` (\C.NodeExists -> return ())
-- Now create our child node in the directory.
let child = path </> "lock-"
let flags = (if isEphemeral then [C.Ephemeral] else []) ++ [C.Sequence]
_ <- C.create handle child value flags C.openAclUnsafe
return ()
-- | Push a (non-ephemeral) value onto the tail of the specified queue.
-- If the client fails then the value will remain in the queue.
push :: C.Handle -- ^ The ZooKeeper handle.
-> String -- ^ The name of the queue node.
-> String -- ^ The value to push onto the queue.
-> IO ()
push = push_ False
-- | Push an ephemeral value onto the tail of the specified queue.
-- If the client fails then the value will be removed from the queue.
pushEphemeral :: C.Handle -- ^ The ZooKeeper handle.
-> String -- ^ The name of the queue node.
-> String -- ^ The ephemeral value to push onto the queue.
-> IO ()
pushEphemeral = push_ True
-- TODO Actually remove the queue when it is empty.
-- | Remove and return the value from the head of the queue. If the queue
-- is currently empty, then this action will block until there is an available
-- value.
pop :: C.Handle -- ^ The ZooKeeper handle.
-> String -- ^ The name of the queue node.
-> IO String -- ^ The value from the head of the queue.
pop h path = do
notified <- newMVar ()
-- TODO Tighten the watcher up.
let watcher _ C.Child _ _ = putMVar notified ()
watcher _ _ _ _ = error "Unexpected response"
f [] = do
takeMVar notified
f =<< sort `liftM` C.getChildren h path (Just watcher)
f (c:cs) = do
x <- E.try $ do
(v, _) <- C.get h (path </> c) Nothing
C.delete h (path </> c) Nothing
return v
case x of
Left C.NoNode -> f cs
Left _ -> error "Unexpected response"
Right v -> return v
f []
-- | Remove and return the value from the head of the queue. If the queue
-- is currently empty, then 'Nothing' will be returned.
popNonBlocking :: C.Handle -- ^ The ZooKeeper handle.
-> String -- ^ The name of the queue node.
-> IO (Maybe String) -- ^ The value from the head of the queue, if present.
popNonBlocking h path = do
let f [] = do
cs <- sort `liftM` C.getChildren h path Nothing
case cs of
[] -> return Nothing -- Queue is empty.
_ -> f cs
f (c:cs) = do
x <- E.try $ do
(v, _) <- C.get h (path </> c) Nothing
C.delete h (path </> c) Nothing
return $ Just v
case x of
Left C.NoNode -> f cs
Left _ -> error "Unexpected response"
Right v -> return v
f []
| jnb/zookeeper | src/Zookeeper/Queue.hs | Haskell | bsd-2-clause | 3,824 |
module C(C.bla) where
import D
bla :: Test
bla = undefined
| nominolo/haddock2 | examples/hide-bug/C.hs | Haskell | bsd-2-clause | 62 |
{-# LANGUAGE ExtendedDefaultRules #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
module Bucket (
uploadObjectFromFile
, uploadObject
, deleteObject
, bucketExists
, createBucket
, deleteBucket
) where
import Control.Lens
import Control.Monad
import Control.Monad.Reader
import Control.Monad.Trans.AWS (AWST, send, send_, info, envRegion)
import Data.Monoid
import Data.Text (Text)
import GHC.Exts
import qualified Network.AWS.S3 as S3
bucketExists :: Text -> AWST IO Bool
bucketExists b = do
bs <- map (view S3.bName) . view S3.lbrBuckets <$> send S3.listBuckets
return $ b `elem` bs
createBucket :: Text -> AWST IO ()
createBucket name = do
e <- bucketExists name
unless e $ do
info ("Creating bucket: " <> name)
region <- asks (view envRegion)
send_ (S3.createBucket name & S3.cbCreateBucketConfiguration ?~ bucketCfg region)
where
bucketCfg region = S3.createBucketConfiguration
& S3.cbcLocationConstraint ?~ region
deleteBucket :: Text -> AWST IO ()
deleteBucket name = do
e <- bucketExists name
when e $ do
info ("Deleting bucket: " <> name)
send_ (S3.deleteBucket name)
uploadObjectFromFile :: Text -> Text -> FilePath -> AWST IO ()
uploadObjectFromFile bucket key file =
liftIO (readFile file) >>= uploadObject bucket key
uploadObject :: Text -> Text -> String -> AWST IO ()
uploadObject bucket key object = do
info ("Creating object: " <> key)
send_ $ S3.putObject (fromString object) bucket key
deleteObject :: Text -> Text -> AWST IO ()
deleteObject bucket key = do
bs <- map (view S3.bName) . view S3.lbrBuckets <$> send S3.listBuckets
when (bucket `elem` bs) $ do
info ("Deleting object: " <> key)
send_ $ S3.deleteObject bucket key
| lbodor/amazonia | src/Bucket.hs | Haskell | bsd-3-clause | 1,974 |
module Core.Typecheck
( QName(..)
, QType
, QTyCon
, QTypes
, QExpr
, QMeta
, QPat
, Renamed
, typecheck
) where
import Control.Arrow (second)
import Data.Map (Map)
import qualified Data.Map as M
import Data.Set (Set)
import qualified Data.Set as S
import qualified Data.IndexedSet as I
import Control.Monad.Reader
import Control.Monad.Writer
import Control.Lens
import qualified Text.PrettyPrint.Leijen.Text as PP
import System.IO.Unsafe
import Debug.Trace
import Core.Types
import Core.Monad
import Core.Pretty
import Core.Typed
type QType = Type QName Name Pos
type QTyCon = TyCon QName Name Pos
type QTyDecl = TyDecl QName Name Pos
type QTypes = Types QName Name Pos
type QExpr = Expr QName Name QMeta
type QMeta = (Pos, [QType])
type QPat = Pat QName Name QMeta
type Renamed = Program QName Name QName Name Pos QMeta
data Scheme' var lit meta = Forall (Set var) (Type var lit meta)
deriving (Show, Eq)
instance MetaTraversal (Scheme' var lit) where
metamap' f (Forall vs t) = Forall vs <$> metamap f t
instance (Pretty var, Pretty lit, Pretty meta) => Pretty (Scheme' var lit meta) where
pretty (Forall vars e) = "β" PP.<+> PP.hsep (map pretty $ S.toList vars) PP.<+> "." PP.<+> pretty e
instance FreeVars (Scheme' QName lit meta) where
ftv (Forall vs t) = ftv t `S.difference` vs
type Scheme var lit meta = Ann meta (Scheme' var lit)
type SubstType' lit meta = Type QName lit meta
type SubstScheme' lit meta = Scheme QName lit meta
type Subst' lit meta = Map QName (SubstType' lit meta)
type Constraint' lit meta = (SubstType' lit meta, SubstType' lit meta)
type SubstType lit = SubstType' lit Pos
type SubstScheme lit = SubstScheme' lit Pos
type Subst lit = Subst' lit Pos
type Constraint lit = Constraint' lit Pos
class Substitutable a where
type SubstLit a
type SubstMeta a
apply :: Subst' (SubstLit a) (SubstMeta a) -> a -> a
instance Substitutable a => Substitutable [a] where
type SubstLit [a] = SubstLit a
type SubstMeta [a] = SubstMeta a
apply = map . apply
instance Substitutable (Subst' lit meta) where
type SubstLit (Subst' lit meta) = lit
type SubstMeta (Subst' lit meta) = meta
apply a b = M.map (apply b) a `M.union` M.map (apply a) b
instance (Substitutable a, Substitutable b, SubstLit a ~ SubstLit b, SubstMeta a ~ SubstMeta b) => Substitutable (a, b) where
type SubstLit (a, b) = SubstLit a
type SubstMeta (a, b) = SubstMeta a
apply s (a, b) = (apply s a, apply s b)
instance Substitutable (TAnn a) where
type SubstLit (TAnn a) = Name
type SubstMeta (TAnn a) = ()
apply s (TName t v) = TName (apply s t) v
instance Substitutable (SubstType' lit meta) where
type SubstLit (SubstType' lit meta) = lit
type SubstMeta (SubstType' lit meta) = meta
apply s t@(Ann _ (TVar v)) = M.findWithDefault t v s
apply _ t@(Ann _ (TLit _)) = t
apply _ t@(Ann _ TFun) = t
apply s (Ann pos (TApp a b)) = Ann pos $ TApp (apply s a) (apply s b)
instance Substitutable (SubstScheme' lit meta) where
type SubstLit (SubstScheme' lit meta) = lit
type SubstMeta (SubstScheme' lit meta) = meta
apply s (Ann pos (Forall as t)) = Ann pos $ Forall as $ apply s' t
where s' = foldr M.delete s as
instance Substitutable TContext where
type SubstLit TContext = Name
type SubstMeta TContext = Pos
apply s = M.map (apply s)
instance FreeVars TContext where
ftv = ftv . M.elems
occursCheck :: FreeVars a => QName -> a -> Bool
occursCheck n t = n `S.member` ftv t
showPA :: (MetaTraversal f, Pretty (f ())) => Ann meta f -> String
showPA = showP . clearAnn
unify :: (Pretty lit, Eq lit) => SubstType lit -> SubstType lit -> Compiler (Subst lit)
unify (Ann _ (TApp a b)) (Ann _ (TApp a' b')) = do
s1 <- unify a a'
s2 <- unify (apply s1 b) (apply s1 b')
return $ apply s2 s1
unify (Ann _ (TVar a)) t = bind a t
unify t (Ann _ (TVar a)) = bind a t
unify (Ann _ (TLit a)) (Ann _ (TLit b)) | a == b = return M.empty
unify (Ann _ TFun) (Ann _ TFun) = return M.empty
unify a@(Ann pos _) b@(Ann _ _) = throwCError pos $ "Cannot unify types: " ++ showPA a ++ " and " ++ showPA b
unifyAll :: (Pretty lit, Eq lit) => [Constraint lit] -> Compiler (Subst lit)
unifyAll [] = return M.empty
unifyAll ((a, b):t) = do
s1 <- unify a b
s2 <- unifyAll (apply s1 t)
--return $ apply s2 s1
return $ apply s2 s1
bind :: QName -> SubstType lit -> Compiler (Subst lit)
bind n (Ann _ (TVar n')) | n == n' = return M.empty
bind n t@(Ann pos _) | occursCheck n t = throwCError pos "Infinite type"
| otherwise = return $ M.singleton n t
type Infer lit = WriterT [Constraint lit] Compiler
uni :: MonadWriter [Constraint lit] m => SubstType lit -> SubstType lit -> m ()
uni t1 t2 = tell [(t1, t2)]
type KType = SubstType ()
type KInfer = Infer ()
type KSubst = Map QName (Kind ())
unsafeQ :: Name -> QName
unsafeQ n = QName n 1
inferKType :: (Pos -> QName -> KType) -> (Pos -> Name -> KType) -> QType -> KInfer ()
inferKType getVar getLit topt@(Ann tpos _) = do
r <- chk topt
uni r $ star tpos
where chk :: QType -> KInfer KType
chk (Ann pos typ) = case typ of
TApp a b -> do
t1 <- chk a
t2 <- chk b
t <- var pos <$> genTemp
uni t1 $ fun pos t2 t
return t
TVar v -> return $ getVar pos v
TLit l -> return $ getLit pos l
TFun -> return $ fun pos (star pos) (fun pos (star pos) (star pos))
ktypeToKind :: SubstType' () meta -> Kind ()
ktypeToKind (Ann _ p) = Ann () $ case p of
-- by default
TVar _ -> Star
TLit _ -> Star
TApp (Ann _ (TApp (Ann _ TFun) a)) b -> KFun (ktypeToKind a) (ktypeToKind b)
_ -> error "ktypeToKind: invalid kind"
kindToKtype :: Pos -> Kind () -> KType
kindToKtype pos (Ann _ Star) = Ann pos $ TLit ()
kindToKtype pos (Ann _ (KFun a b)) = fun pos (kindToKtype pos a) (kindToKtype pos b)
inferKinds :: QTypes -> Compiler TTypes
inferKinds typs = do
constraints <- execWriterT $ mapM inferKind $ I.toList typs
ss <- unifyAll constraints
return $ I.fromList $ map (applyKind $ M.map ktypeToKind ss) $ I.toList typs
where applyKind :: KSubst -> QTyDecl -> TTyDecl
applyKind subst (Ann _ (TyDecl name vars constrs)) =
Ann () $ TyDecl (KName (subst M.! unsafeQ name) name) (map (\v -> KName (subst M.! v) v) vars) (map (applyConstr subst) constrs)
applyConstr subst (Ann _ (TyCon name pars)) =
Ann () $ TyCon (KName (Ann () Star) name) (map (applyPar subst) pars)
applyPar subst = chk
where chk (Ann _ p) = Ann () $ case p of
TVar v -> TVar $ KName (subst M.! v) v
TLit l -> TLit $ KName (subst M.! unsafeQ l) l
TFun -> TFun
TApp a b -> TApp (chk a) (chk b)
inferKind :: QTyDecl -> KInfer ()
inferKind (Ann pos (TyDecl name vars constrs)) = do
let typ = var pos $ unsafeQ name
ttyp = foldr (fun pos . var pos) (star pos) vars
uni typ ttyp
mapM_ (\(Ann _ (TyCon _ pars)) -> mapM_ inferPar pars) constrs
inferPar :: QType -> KInfer ()
inferPar = inferKType var (\p n -> var p $ unsafeQ n)
kindCheck :: TTypes -> QType -> Compiler ()
kindCheck typs typ = do
constraints <- execWriterT $ inferKType' typ
void $ unifyAll constraints
where getLit pos name = kindToKtype pos kind
where (Ann _ (TyDecl (KName kind _) _ _)) = typs I.! name
inferKType' = inferKType var getLit
annsCheck :: TTypes -> QExpr -> Compiler ()
annsCheck typs expr = void (expr & metamap %%~ chk)
where chk :: QMeta -> Compiler QMeta
chk r@(_, anns) = do
mapM_ (kindCheck typs) anns
return r
type ConstrType = Type QName Name ()
type ConstrScheme = Scheme QName Name ()
type Constrs = Map Name Constr
type Constr = (ConstrScheme, [ConstrType])
buildConstrs :: QTypes -> Constrs
buildConstrs = M.fromList . concatMap getConstrs . I.toList
where getConstrs :: QTyDecl -> [(Name, Constr)]
getConstrs (Ann _ (TyDecl tname vars constrs)) = map mkcon constrs
where ftype :: ConstrScheme
ftype = Ann () $ Forall (S.fromList vars) $ foldl (\t a -> app () t (var () a)) (lit () tname) vars
mkcon :: QTyCon -> (Name, Constr)
mkcon (Ann _ (TyCon name pars)) = (name, (ftype, ptyps))
where ptyps :: [ConstrType]
ptyps = map clearAnn pars
type TInfer = ReaderT TContext (Infer Name)
type TSubst = Subst' Name ()
type TSubstType = SubstType Name
type TSubstScheme = SubstScheme Name
type TContext = Map QName TSubstScheme
type ITPat = Pat TQName TName Pos
type ITExpr = Expr TQName TName Pos
instVar :: QName -> TInfer QName
instVar (QName n _) = QName n <$> genTemp
instantiate :: TSubstScheme -> TInfer TSubstType
instantiate (Ann pos (Forall (S.toList -> as) t)) = do
as' <- mapM (liftM (var pos) . instVar) as
let s = M.fromList $ zip as as'
return $ apply s t
generalize :: TContext -> TSubstType -> TSubstScheme
generalize env t@(Ann pos _) = let a = Ann pos $ Forall as t in trace ("generalize: " ++ show a) a
where as = ftv t S.\\ ftv env
-- TODO: a better inference engine:
-- * convert entire tree into ITExpr (with some initial type variables everywhere)
-- * iterate while there's something untraversed:
-- * collect constraints until we hit into a Let or a leaf
-- * solve constraints
-- * use new substitution to infer types of let bindings
-- * mark those Lets as traversed (keep set of any one variable names from Lets, skip them on encounter)
inferType :: Constrs -> QExpr -> Compiler TExpr
inferType constrs expr = do
((_, expr'), constraints) <- runWriterT (runReaderT (inferExpr expr) M.empty)
let pr c = pretty (clearAnn c)
let constraints' = unsafePerformIO $ do
printDoc $ PP.vsep $ map (\(a, b) -> pretty a PP.<+> "::" PP.<+> pretty b) $ M.toList constrs
printDoc $ PP.vsep $ map (\(a, b) -> pr a PP.<+> "~" PP.<+> pr b) constraints
return constraints
cs <- unifyAll constraints'
let cs' = unsafePerformIO $ do
printDoc $ PP.vsep $ map (\(a, b) -> pretty a PP.<+> "->" PP.<+> pr b) $ M.toList cs
return cs
return $ applyExpr (M.map clearAnn cs') expr'
where getSubst :: TSubst -> TAnn a -> TAnn a
getSubst subst (TName t n) = TName (apply subst t) n
applyExpr :: TSubst -> TExpr -> TExpr
applyExpr subst (Ann _ p) = Ann () $ case p of
Var n -> Var (getSubst subst n)
Lit n -> Lit (getSubst subst n)
Builtin n -> Lit (getSubst subst n)
Int i -> Int i
Abs n e -> Abs (getSubst subst n) (applyExpr subst e)
App e1 e2 -> App (applyExpr subst e1) (applyExpr subst e2)
Let ns e -> Let (applyExpr subst <$> M.mapKeys (apply subst) ns) (applyExpr subst e)
Case sc as -> Case (applyExpr subst sc) (map (\(pt, e) -> (applyPat subst pt, applyExpr subst e)) as)
applyPat :: TSubst -> TPat -> TPat
applyPat subst (Ann _ p) = Ann () $ case p of
(PVar v) -> PVar $ getSubst subst v
(PCon v ps) -> PCon (getSubst subst v) (map (applyPat subst) ps)
inEnv :: QName -> TSubstScheme -> TInfer a -> TInfer a
inEnv name s = local (M.insert name s)
constrFun :: Pos -> Constr -> TInfer TSubstType
constrFun pos (Ann _ (Forall vars ftype), ptyps) =
instantiate $ Ann pos $ Forall vars (foldr (fun ()) ftype ptyps & metamap .~ pos)
inferPat :: QPat -> TInfer (TContext, TSubstType, TPat)
inferPat (Ann (pos, anns) p) = do
r@(_, typ, _) <- case p of
PVar v -> do
let tv = var pos v
return (M.singleton v $ Ann pos $ Forall S.empty tv, tv, Ann () $ PVar $ TName (clearAnn tv) v)
PCon name pats -> do
let (Ann _ (Forall vars ctyp), ts) = constrs M.! name
-- want this in the library!
let fromSetM f = liftM M.fromList . mapM (\n -> (n, ) <$> f n) . S.toList
subst <- fromSetM (\n -> var () <$> instVar n) vars
(ctxs, pats') <- liftM unzip $ forM (zip pats ts) $ \(pt, t) -> do
(ctx, typ, pt') <- inferPat pt
let t' = apply subst t & metamap .~ pos
uni typ t'
return (ctx, pt')
let ctx = foldr M.union M.empty ctxs
ctyp' = apply subst ctyp & metamap .~ pos
name' = TName (clearAnn ctyp') name
return (ctx, ctyp', Ann () $ PCon name' pats')
mapM_ (uni typ) anns
return r
inferExpr :: QExpr -> TInfer (TSubstType, TExpr)
inferExpr (Ann (pos, anns) expr') = do
(typ, expr'') <- case expr' of
Var x -> do
env <- ask
t <- instantiate $ env M.! x
return (t, Var $ TName (clearAnn t) x)
Lit l -> do
let c = constrs M.! l
t <- constrFun pos c
return (t, Lit $ TName (clearAnn t) l)
-- type info is contained in the annotation for builtin things
Builtin n -> do
t <- var pos <$> genTemp
return (t, Builtin $ TName (clearAnn t) n)
Int i -> do
t <- var pos <$> genTemp
return (t, Int i)
Abs x e -> do
let tv = var pos x
(t', e') <- inEnv x (Ann pos $ Forall S.empty tv) $ inferExpr e
let t = fun pos tv t'
return (t, Abs (TName (clearAnn tv) x) e')
App e1 e2 -> do
(t1, e1') <- inferExpr e1
(t2, e2') <- inferExpr e2
t <- var pos <$> genTemp
uni t1 (fun pos t2 t)
return (t, App e1' e2')
Let ns e -> do
let vars = M.mapWithKey (\n (Ann (lpos, _) _) -> var lpos n) ns
env <- ask
ns' <-
local (M.union $ fmap (Ann pos . Forall S.empty) vars) $
liftM M.fromList $ forM (M.toList ns) $ \(n, ne@(Ann (_, lanns) _)) -> do
let typ = vars M.! n
(nt, ne') <- inferExpr ne
mapM_ (uni typ) lanns
uni typ nt
return (TName (clearAnn typ) n, ne')
-- FIXME: enable generalization back and implement engine properly instead (see above)
--(t, e') <- local (M.union $ fmap (generalize env) vars) $ inferExpr e
(t, e') <- local (M.union $ fmap (Ann pos . Forall S.empty) vars) $ inferExpr e
return (t, Let ns' e')
Case scr alts -> do
(te, scr') <- inferExpr scr
t <- var pos <$> genTemp
alts' <- forM alts $ \(pat, e) -> do
(ctx, typ, pat') <- inferPat pat
uni te typ
(tp, e') <- local (M.union ctx) $ inferExpr e
uni tp t
return (pat', e')
return (t, Case scr' alts')
mapM_ (uni typ) anns
return (typ, Ann () expr'')
-- FIXME: finish and use for better inference
splitLets :: QExpr -> QExpr
splitLets (Ann pos expr) = Ann pos $ case expr of
Let ns e -> undefined
Var v -> Var v
Lit l -> Lit l
Builtin n -> Builtin n
Int i -> Int i
Abs v e -> Abs v $ splitLets e
App e1 e2 -> App (splitLets e1) (splitLets e2)
Case e alts -> Case (splitLets e) (map (second splitLets) alts)
typecheck :: Renamed -> Compiler Typechecked
typecheck prog = do
kinded <- inferKinds $ progTypes prog
annsCheck kinded $ progExpr prog
let constrs = buildConstrs $ progTypes prog
typed <- inferType constrs $ progExpr prog
return $ Program { progTypes = kinded
, progExpr = typed
}
| abbradar/dnohs | src/Core/Typecheck.hs | Haskell | bsd-3-clause | 16,102 |
{-# LANGUAGE ForeignFunctionInterface, CPP #-}
--------------------------------------------------------------------------------
-- |
-- Module : Graphics.Rendering.OpenGL.Raw.ARB.ShaderSubroutine
-- Copyright : (c) Sven Panne 2014
-- License : BSD3
--
-- Maintainer : Sven Panne <[email protected]>
-- Stability : stable
-- Portability : portable
--
-- All raw functions and tokens from the ARB_shader_subroutine extension, see
-- <http://www.opengl.org/registry/specs/ARB/shader_subroutine.txt>.
--
--------------------------------------------------------------------------------
module Graphics.Rendering.OpenGL.Raw.ARB.ShaderSubroutine (
-- * Functions
glGetSubroutineUniformLocation,
glGetSubroutineIndex,
glGetActiveSubroutineUniformiv,
glGetActiveSubroutineUniformName,
glGetActiveSubroutineName,
glUniformSubroutinesuiv,
glGetUniformSubroutineuiv,
glGetProgramStageiv,
-- * Tokens
gl_ACTIVE_SUBROUTINES,
gl_ACTIVE_SUBROUTINE_UNIFORMS,
gl_ACTIVE_SUBROUTINE_UNIFORM_LOCATIONS,
gl_ACTIVE_SUBROUTINE_MAX_LENGTH,
gl_ACTIVE_SUBROUTINE_UNIFORM_MAX_LENGTH,
gl_MAX_SUBROUTINES,
gl_MAX_SUBROUTINE_UNIFORM_LOCATIONS,
gl_NUM_COMPATIBLE_SUBROUTINES,
gl_COMPATIBLE_SUBROUTINES,
gl_UNIFORM_SIZE,
gl_UNIFORM_NAME_LENGTH
) where
import Foreign.C.Types
import Foreign.Ptr
import Graphics.Rendering.OpenGL.Raw.ARB.UniformBufferObject
import Graphics.Rendering.OpenGL.Raw.Core31.Types
import Graphics.Rendering.OpenGL.Raw.Extensions
--------------------------------------------------------------------------------
#include "HsOpenGLRaw.h"
extensionNameString :: String
extensionNameString = "GL_ARB_shader_subroutine"
EXTENSION_ENTRY(dyn_glGetSubroutineUniformLocation,ptr_glGetSubroutineUniformLocation,"glGetSubroutineUniformLocation",glGetSubroutineUniformLocation,GLuint -> GLenum -> Ptr GLchar -> IO GLint)
EXTENSION_ENTRY(dyn_glGetSubroutineIndex,ptr_glGetSubroutineIndex,"glGetSubroutineIndex",glGetSubroutineIndex,GLuint -> GLenum -> Ptr GLchar -> IO GLuint)
EXTENSION_ENTRY(dyn_glGetActiveSubroutineUniformiv,ptr_glGetActiveSubroutineUniformiv,"glGetActiveSubroutineUniformiv",glGetActiveSubroutineUniformiv,GLuint -> GLenum -> GLuint -> GLenum -> Ptr GLint -> IO ())
EXTENSION_ENTRY(dyn_glGetActiveSubroutineUniformName,ptr_glGetActiveSubroutineUniformName,"glGetActiveSubroutineUniformName",glGetActiveSubroutineUniformName,GLuint -> GLenum -> GLuint -> GLsizei -> Ptr GLsizei -> Ptr GLchar -> IO ())
EXTENSION_ENTRY(dyn_glGetActiveSubroutineName,ptr_glGetActiveSubroutineName,"glGetActiveSubroutineName",glGetActiveSubroutineName,GLuint -> GLenum -> GLuint -> GLsizei -> Ptr GLsizei -> Ptr GLchar -> IO ())
EXTENSION_ENTRY(dyn_glUniformSubroutinesuiv,ptr_glUniformSubroutinesuiv,"glUniformSubroutinesuiv",glUniformSubroutinesuiv,GLenum -> GLsizei -> Ptr GLuint -> IO ())
EXTENSION_ENTRY(dyn_glGetUniformSubroutineuiv,ptr_glGetUniformSubroutineuiv,"glGetUniformSubroutineuiv",glGetUniformSubroutineuiv,GLenum -> GLint -> Ptr GLuint -> IO ())
EXTENSION_ENTRY(dyn_glGetProgramStageiv,ptr_glGetProgramStageiv,"glGetProgramStageiv",glGetProgramStageiv,GLuint -> GLenum -> GLenum -> Ptr GLint -> IO ())
gl_ACTIVE_SUBROUTINES :: GLenum
gl_ACTIVE_SUBROUTINES = 0x8DE5
gl_ACTIVE_SUBROUTINE_UNIFORMS :: GLenum
gl_ACTIVE_SUBROUTINE_UNIFORMS = 0x8DE6
gl_ACTIVE_SUBROUTINE_UNIFORM_LOCATIONS :: GLenum
gl_ACTIVE_SUBROUTINE_UNIFORM_LOCATIONS = 0x8E47
gl_ACTIVE_SUBROUTINE_MAX_LENGTH :: GLenum
gl_ACTIVE_SUBROUTINE_MAX_LENGTH = 0x8E48
gl_ACTIVE_SUBROUTINE_UNIFORM_MAX_LENGTH :: GLenum
gl_ACTIVE_SUBROUTINE_UNIFORM_MAX_LENGTH = 0x8E49
gl_MAX_SUBROUTINES :: GLenum
gl_MAX_SUBROUTINES = 0x8DE7
gl_MAX_SUBROUTINE_UNIFORM_LOCATIONS :: GLenum
gl_MAX_SUBROUTINE_UNIFORM_LOCATIONS = 0x8DE8
gl_NUM_COMPATIBLE_SUBROUTINES :: GLenum
gl_NUM_COMPATIBLE_SUBROUTINES = 0x8E4A
gl_COMPATIBLE_SUBROUTINES :: GLenum
gl_COMPATIBLE_SUBROUTINES = 0x8E4B
| mfpi/OpenGLRaw | src/Graphics/Rendering/OpenGL/Raw/ARB/ShaderSubroutine.hs | Haskell | bsd-3-clause | 3,916 |
{-# LANGUAGE CPP #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DefaultSignatures #-}
module Data.Var.Boxed
( MonadVar (..)
, contents
, modify
) where
import Control.Applicative
import Control.Lens
import qualified Control.Monad.ST.Lazy.Safe as Lazy
import Control.Monad.ST.Safe
import Control.Monad.Trans.Class
import Control.Monad.Trans.Cont
import Control.Monad.Trans.Error
import Control.Monad.Trans.Identity
import Control.Monad.Trans.List
import Control.Monad.Trans.Maybe
import qualified Control.Monad.Trans.RWS.Lazy as Lazy
import Control.Monad.Trans.RWS.Strict (RWST)
import Control.Monad.Trans.Reader
import qualified Control.Monad.Trans.State.Lazy as Lazy
import Control.Monad.Trans.State.Strict (StateT)
import qualified Control.Monad.Trans.Writer.Lazy as Lazy
import Control.Monad.Trans.Writer.Strict
import Data.IORef
import Data.Monoid
import Data.STRef
import qualified Data.STRef.Lazy as Lazy
import Prelude (IO, Monad (..), (.))
class (Applicative m, Monad m) => MonadVar m where
type Var m :: * -> *
new :: a -> m (Var m a)
read :: Var m a -> m a
write :: Var m a -> a -> m ()
#ifndef HLINT
default new :: (MonadTrans t, MonadVar m) => a -> t m (Var m a)
{-# INLINE new #-}
new = lift . new
#endif
#ifndef HLINT
default read :: (MonadTrans t, MonadVar m) => Var m a -> t m a
{-# INLINE read #-}
read = lift . read
#endif
#ifndef HLINT
default write :: (MonadTrans t, MonadVar m) => Var m a -> a -> t m ()
{-# INLINE write #-}
write var = lift . write var
#endif
contents :: MonadVar m => IndexPreservingAction m (Var m a) a
{-# INLINE contents #-}
contents = act read
modify :: MonadVar m => Var m a -> (a -> a) -> m ()
{-# INLINE modify #-}
modify var f = read var >>= write var . f
instance MonadVar (ST s) where
type Var (ST s) = STRef s
{-# INLINE new #-}
new = newSTRef
{-# INLINE read #-}
read = readSTRef
{-# INLINE write #-}
write = writeSTRef
instance MonadVar (Lazy.ST s) where
type Var (Lazy.ST s) = STRef s
{-# INLINE new #-}
new = Lazy.newSTRef
{-# INLINE read #-}
read = Lazy.readSTRef
{-# INLINE write #-}
write = Lazy.writeSTRef
instance MonadVar IO where
type Var IO = IORef
{-# INLINE new #-}
new = newIORef
{-# INLINE read #-}
read = readIORef
{-# INLINE write #-}
write = writeIORef
instance MonadVar m => MonadVar (ContT r m) where
type Var (ContT r m) = Var m
instance (Error e, MonadVar m) => MonadVar (ErrorT e m) where
type Var (ErrorT e m) = Var m
instance MonadVar m => MonadVar (IdentityT m) where
type Var (IdentityT m) = Var m
instance MonadVar m => MonadVar (ListT m) where
type Var (ListT m) = Var m
instance MonadVar m => MonadVar (MaybeT m) where
type Var (MaybeT m) = Var m
instance (Monoid w, MonadVar m) => MonadVar (Lazy.RWST r w s m) where
type Var (Lazy.RWST r w s m) = Var m
instance (Monoid w, MonadVar m) => MonadVar (RWST r w s m) where
type Var (RWST r w s m) = Var m
instance MonadVar m => MonadVar (ReaderT r m) where
type Var (ReaderT r m) = Var m
instance MonadVar m => MonadVar (Lazy.StateT s m) where
type Var (Lazy.StateT s m) = Var m
instance MonadVar m => MonadVar (StateT s m) where
type Var (StateT s m) = Var m
instance (Monoid w, MonadVar m) => MonadVar (Lazy.WriterT w m) where
type Var (Lazy.WriterT w m) = Var m
instance (Monoid w, MonadVar m) => MonadVar (WriterT w m) where
type Var (WriterT w m) = Var m
| sonyandy/wart-var | src/Data/Var/Boxed.hs | Haskell | bsd-3-clause | 3,430 |
{-|
Module : Database.Taxi.Segment.Types
Description : Type definitions
Stability : Experimental
Maintainer : [email protected]
-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE RecordWildCards #-}
module Database.Taxi.Segment.Types where
import Control.Applicative ((<$>), (<*>))
import Data.Binary (Binary, put, get)
import Data.ByteString (ByteString)
import Data.Set (Set)
import Data.Trie (Trie)
import Data.UUID (UUID)
import GHC.Int (Int64)
import Database.Taxi.Segment.BinaryHelper
-- | Offset (bytes) into the file
type Offset = Int64
newtype Dictionary p = Dictionary { unDict :: Trie Offset }
deriving Binary
type SegmentId = UUID
data InMemorySegment p = InMemorySegment (Trie (Set p))
data ExternalSegment p = ExternalSegment { segmentId :: SegmentId
, dictionary :: Dictionary p
}
-- | __IIEntry__ stands for Inverted Index Entry and is the basic unit of an inverted index.
-- It is a mapping from term to postings list where additionally
-- posting(s) are stored in sorted order for easier manipulation
data IIEntry p = IIEntry { iiTerm :: ByteString
-- ^ key (string) for this term
, iiPostingsList :: [p]
-- ^ List of posting corresponding to this key
} deriving Show
instance Binary p => Binary (IIEntry p) where
put IIEntry{..} = put iiTerm >> putListOf put iiPostingsList
get = IIEntry <$> get <*> getListOf get
| rabisg/taxi | Database/Taxi/Segment/Types.hs | Haskell | bsd-3-clause | 1,720 |
{-#LANGUAGE MonoLocalBinds #-}
module LambdaF2 where
import Name
import Value
import Lambda as Lam
import Data.Bifunctor
data LamTermF i j n a = LambdaF [(i, Name)] a
| ApplF a [a]
| VarF j n
| ValF j Value
| LetF j [Def i a] a
deriving (Eq, Show)
instance Functor (LamTermF i j n) where
fmap f (LambdaF v t) = LambdaF v $ f t
fmap f (ApplF t1 ts) = ApplF (f t1) (fmap f ts)
fmap _ (VarF i n) = VarF i n
fmap _ (ValF i v) = ValF i v
fmap f (LetF i defs t ) = LetF i (map (fmap f) defs) $ f t
instance Traversable (LamTermF i j n) where
traverse _ (VarF i b) = pure (VarF i b)
traverse _ (ValF i v) = pure (ValF i v)
traverse f (LambdaF v t) = LambdaF v <$> f t
traverse f (ApplF t1 ts) = ApplF <$> f t1 <*> traverse f ts
traverse f (LetF i defs tn) = LetF i <$> traverse (traverse f ) defs <*> f tn
instance Foldable (LamTermF i j n) where
foldr _ b VarF {} = b
foldr _ b ValF {} = b
foldr f b (LambdaF _ a) = f a b
foldr f b (ApplF a1 as) = f a1 (foldr f b as)
foldr f b (LetF _ defs an) = foldr (flip (foldr f) ) (f an b) defs
wrap :: LamTerm i j n -> LamTermF i j n (LamTerm i j n)
wrap (Lam.Var i n) = VarF i n
wrap (Lam.Val i v) = ValF i v
wrap [email protected] {} = LambdaF v t
where
(v, t) = go t0
go (Lam.Lambda i n tn) = first ((i,n):) $ go tn
go tn = ([],tn)
wrap [email protected] {} = let (f:args)= accumulateArgs t0
in ApplF f args
wrap (Lam.Let i defs t) = LetF i defs t
unwrap :: LamTermF i j n (LamTerm i j n) -> LamTerm i j n
unwrap (VarF i n) = Var i n
unwrap (ValF i v) = Val i v
unwrap (LambdaF ns t) = foldr (\(i, n) -> Lambda i n ) t ns
unwrap (ApplF t1 ts) = foldl Appl t1 ts
unwrap (LetF i defs t) = Let i defs t
mapLambdaM :: Monad m
=> (LamTerm i j n -> LamTermF i j n a -> m a)
-> LamTerm i j n
-> m a
mapLambdaM f ast0 = go ast0
where
go ast = do
astF <- traverse go $ wrap ast
f ast astF
foldLambdaM :: Monad m
=> (context -> LamTerm i j n -> LamTermF i j n (context -> m a) -> m a)
-> context
-> LamTerm i j n
-> m a
foldLambdaM f context0 ast0 = go ast0 context0
where
go ast context = case ast of
Var i n -> f context ast (VarF i n)
Val i v -> f context ast (ValF i v)
_ -> f context ast $ fmap go (wrap ast)
bottumUpWithM :: Monad m
=> (context -> LamTerm i j n -> m context)
-> (context -> LamTerm i j n -> LamTermF i j n a -> m a)
-> context
-> LamTerm i j n
-> m a
bottumUpWithM updateContext f context0 ast0 = go context0 ast0
where
-- go :: context -> LamTerm i n -> m a
go context ast = do
newContext <- updateContext context ast
astF <- traverse (go newContext) (wrap ast)
f newContext ast astF
bottumUpWith :: (context -> LamTerm i j n -> context)
-> (context -> LamTerm i j n -> LamTermF i j n a -> a)
-> context
-> LamTerm i j n
-> a
bottumUpWith updateContext f context0 ast0 = go context0 ast0
where
-- go :: context -> LamTerm i n -> a
go context ast = f newContext ast (go newContext <$> wrap ast)
where
newContext = updateContext context ast
| kwibus/myLang | src/LambdaF2.hs | Haskell | bsd-3-clause | 3,321 |
module LessWrong.COC.Error where
import Data.Text (unpack)
import LessWrong.COC.Type
import LessWrong.COC.Pretty
data CalculusError = ParsingError String
| UnknownVariable Var
| CannotEqualize Term Term
| InvalidType Term String
instance Show CalculusError where
show (ParsingError txt) = "Parsing error:\n" ++ txt
show (UnknownVariable (V v)) = "Variable '" ++ unpack v ++ "' is not defined"
show (CannotEqualize t t') = "Cannot equalize types '" ++ pretty t ++ "' and '" ++ pretty t' ++ "'"
show (InvalidType t r) = "Type '" ++ pretty t ++ "' is invalid (reason: " ++ r ++ ")"
| zmactep/less-wrong | src/LessWrong/COC/Error.hs | Haskell | bsd-3-clause | 702 |
module Minimax
where
import Debug.Trace
import Data.List
import Data.Ord
class GameState a where
evaluateState :: a -> Int
terminalState :: a -> Bool
genSuccessors :: a -> [Int]
makeSuccessor :: a -> Int -> a
isMaximizing :: a -> Bool
minimax :: (GameState a) => a -> Bool -> Int -> Int -> (Int, Maybe Int)
minimax gs _ depth depthlimit | depth == depthlimit || terminalState gs = (evaluateState gs, Nothing)
minimax gs minimize depth depthlimit =
let minOrMax = (if minimize then minimumBy else maximumBy) (comparing fst)
successors = (genSuccessors gs)
scores = map fst $ map (\succ -> (minimax (makeSuccessor gs succ) (not minimize) (depth+1) depthlimit)) successors
wrappedSuccessors = map Just successors
scoreSuccPairs = zip scores wrappedSuccessors in
minOrMax scoreSuccPairs
{- alphabetafold :: (GameState a) => a -> [Int] -> Int -> Int -> Int -> Int -> Int
alphabetafold _ [] alpha _ _ _ = alpha
alphabetafold gs (x:xs) alpha beta depth depthlimit =
let child = makeSuccessor gs x
newAlpha = negate $ alphabeta child (depth+1) depthlimit (-beta) (-alpha) in
if (beta <= newAlpha)
then alpha
else alphabetafold gs xs (max alpha newAlpha) beta depth depthlimit -}
alphabeta :: (GameState a) => a -> Int -> Int -> Int -> Int -> (Int, Maybe Int)
alphabeta gs _ _ _ _ | terminalState gs = (evaluateState gs, Nothing)
alphabeta gs depth depthlimit _ _ | depth == depthlimit = (evaluateState gs, Nothing)
alphabeta gs depth depthlimit alpha beta =
alphabetafold successors alpha beta (-1)
where successors = genSuccessors gs
alphabetafold [] a _ bestChild = (a, Just bestChild)
alphabetafold (x:xs) a b bestChild =
let child = makeSuccessor gs x
newAlpha = (if (isMaximizing child) then alphabetamax else alphabetamin) child (depth+1) depthlimit a b in
if (newAlpha >= b)
then (newAlpha, Just x)
else alphabetafold xs (max a newAlpha) b (if newAlpha > a then x else bestChild)
{-alphabeta :: (GameState a) => a -> Int -> Int -> Int -> Int -> (Int, Maybe Int)
alphabeta gs _ _ _ _ | terminalState gs = (evaluateState gs, Nothing)
alphabeta gs depth depthlimit _ _ | depth == depthlimit = (evaluateState gs, Nothing)
alphabeta gs depth depthlimit alpha beta =
alphabetafold successors alpha beta (-1)
where successors = genSuccessors gs
alphabetafold [] a _ bestChild = (a, Just bestChild)
alphabetafold (x:xs) a b bestChild =
let child = makeSuccessor gs x
(newAlph, _) = alphabeta child (depth+1) depthlimit (negate b) (negate a)
newAlpha = negate newAlph in
if (newAlpha >= b)
then (newAlpha, Just x)
else alphabetafold xs (max a newAlpha) b (if newAlpha > a then x else bestChild)
-}
alphabetamax :: (GameState a) => a -> Int -> Int -> Int -> Int -> Int
alphabetamax gs _ _ _ _ | terminalState gs = evaluateState gs
alphabetamax gs depth depthlimit _ _ | depth == depthlimit = evaluateState gs
alphabetamax gs depth depthlimit alpha beta =
alphabetafold successors alpha beta
where successors = genSuccessors gs
alphabetafold [] a _ = a
alphabetafold (x:xs) a b =
let child = makeSuccessor gs x
newAlpha = (if (isMaximizing child) then alphabetamax else alphabetamin) child (depth+1) depthlimit a b in
if (newAlpha >= b)
then newAlpha
else alphabetafold xs (max a newAlpha) b
alphabetamin :: (GameState a) => a -> Int -> Int -> Int -> Int -> Int
alphabetamin gs _ _ _ _ | terminalState gs = evaluateState gs
alphabetamin gs depth depthlimit _ _ | depth == depthlimit = evaluateState gs
alphabetamin gs depth depthlimit alpha beta =
alphabetafold successors alpha beta
where successors = genSuccessors gs
alphabetafold [] _ b = b
alphabetafold (x:xs) a b =
let child = makeSuccessor gs x
newBeta = (if (isMaximizing child) then alphabetamax else alphabetamin) child (depth+1) depthlimit a b in
if (newBeta <= a)
then newBeta
else alphabetafold xs a (min b newBeta)
| tylerprete/haskell-minimax-games | src/minimax.hs | Haskell | bsd-3-clause | 4,358 |
{-# OPTIONS_GHC -Wall #-}
module Main where
import Graphics.Gloss
import Physics.Learn.CarrotVec
import Physics.Learn.Position
import Physics.Learn.Curve
import Physics.Learn.Charge
import Physics.Learn.Visual.GlossTools
pixelsPerMeter :: Float
pixelsPerMeter = 40
pixelsPerVPM :: Float
pixelsPerVPM = 5.6
scalePoint :: Float -> Point -> Point
scalePoint m (x,y) = (m*x,m*y)
twoD :: Vec -> Point
twoD r = (realToFrac $ xComp r,realToFrac $ yComp r)
twoDp :: Position -> Point
twoDp r = (realToFrac x, realToFrac y)
where
(x,y,_) = cartesianCoordinates r
samplePoints :: [Position]
samplePoints = [cart x y 0 | x <- [-8,-6..8], y <- [-6,-4..6], abs y > 0.5 || abs x > 4.5]
curve1 :: Curve
curve1 = Curve (\t -> cart t 0 0) (-4) 4
eFields :: [(Position,Vec)]
eFields = [(r,eFieldFromLineCharge (const 1e-9) curve1 r) | r <- samplePoints]
arrows :: [Picture]
arrows = [thickArrow 5 (scalePoint pixelsPerMeter $ twoDp r)
(scalePoint pixelsPerVPM $ twoD e) | (r,e) <- eFields]
main :: IO ()
main = display (InWindow "Electric Field from a Line Charge" (680,520) (10,10)) white $
Pictures [(Color blue (Pictures arrows))
,Color orange $ Line [(-4*pixelsPerMeter,0),(4*pixelsPerMeter,0)]]
| walck/learn-physics | examples/src/eFieldLine2D.hs | Haskell | bsd-3-clause | 1,252 |
{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-}
module Evaluate(normalise) where
import Debug.Trace
import Core
normalise :: Context -> TT Name -> TT Name
normalise ctxt t = quote 0 (eval ctxt (hoas [] t))
-- We just evaluate HOAS terms. Any de Bruijn indices will refer to higher
-- level things, so, if we remove a binder, we need to strengthen the
-- indices appropriately.
eval :: Context -> HTT -> HTT
eval ctxt t = ev t where
ev (HP Ref n ty)
| Just v <- lookupVal n ctxt = v -- FIXME! Needs evalling
ev (HP nt n ty) = HP nt n (ev ty)
ev (HApp f t a)
= evSpine f [(a, t)]
where evSpine (HApp f t a) sp = evSpine f ((a, t):sp)
evSpine f sp = evAp f sp
ev (HBind n (Let t v) sc) = weaken (-1) (ev (sc (weaken 1 (ev v))))
ev (HBind n b sc)
= HBind n (evB b) (\x -> ev (sc x))
where evB (Lam t) = Lam (ev t)
evB (Pi t) = Pi (ev t)
evB (Hole t) = Hole (ev t)
evB (Guess t v) = Guess (ev t) (ev v)
evB (PVar t) = PVar (ev t)
ev tm = tm -- Constructors + constants
-- TODO:add PE magic here - nothing is evaluated yet
evAp f sp = evAp' (ev f) sp
evAp' (HBind n (Lam ty) sc) ((a, t):sp)
= weaken (-1) (evAp' (sc (weaken 1 (ev a))) sp)
evAp' f sp = apply f (map (\ (a, t) -> (ev a, ev t)) sp)
apply f [] = f
apply f ((a, t):xs) = apply (HApp f t a) xs
weaken :: Int -> HTT -> HTT
weaken w (HV i) = HV (i + w)
weaken w (HBind n b sc)
= HBind n (weakenB b) (\x -> weaken w (sc x))
where weakenB (Lam t) = Lam (weaken w t)
weakenB (Pi t) = Pi (weaken w t)
weakenB (Let t v) = Let (weaken w t) (weaken w v)
weakenB (Hole t) = Hole (weaken w t)
weakenB (Guess t v) = Guess (weaken w t) (weaken w v)
weakenB (PVar t) = PVar (weaken w t)
weaken w (HApp f t a) = HApp (weaken w f) (weaken w t) (weaken w a)
weaken w tm = tm
quote :: Int -> HTT -> TT Name
quote env (HP nt n t) = P nt n (quote env t)
quote env (HV i) = V i
quote env (HBind n b sc)
= Bind n (quoteB b) (quote (env+1) (sc (HTmp (env+1))))
where quoteB (Lam t) = Lam (quote env t)
quoteB (Pi t) = Pi (quote env t)
quoteB (Let t v) = Let (quote env t) (quote env v)
quoteB (Hole t) = Hole (quote env t)
quoteB (Guess t v) = Guess (quote env t) (quote env v)
quoteB (PVar t) = PVar (quote env t)
quote env (HApp f t a) = App (quote env f) (quote env t) (quote env a)
quote env (HSet i) = Set i
quote env (HTmp i) = V (env-i)
| jxwr/hdep | src/Evaluate.hs | Haskell | bsd-3-clause | 2,525 |
{-# LANGUAGE CPP, ForeignFunctionInterface #-}
{-
A large and somewhat miscellaneous collection of utility functions used
throughout the rest of libfaction and in other tools that use it, like
@faction@. It has a very simple set of logging actions. It has low level
functions for running programs, a bunch of wrappers for various directory
and file functions that do extra logging.
-}
module Distribution.Simple.Utils (
factionVersion,
-- * logging and errors
die,
dieWithLocation,
topHandler,
warn, notice, setupMessage, info, debug,
chattyTry,
-- * running programs
rawSystemExit,
rawSystemExitCode,
rawSystemExitWithEnv,
rawSystemStdout,
rawSystemStdInOut,
maybeExit,
xargs,
findProgramLocation,
findProgramVersion,
-- * copying files
smartCopySources,
createDirectoryIfMissingVerbose,
copyFileVerbose,
copyDirectoryRecursiveVerbose,
copyFiles,
-- * installing files
installOrdinaryFile,
installExecutableFile,
installOrdinaryFiles,
installDirectoryContents,
-- * File permissions
setFileOrdinary,
setFileExecutable,
-- * file names
currentDir,
-- * finding files
findFile,
findFirstFile,
findFileWithExtension,
findFileWithExtension',
findModuleFile,
findModuleFiles,
getDirectoryContentsRecursive,
-- * simple file globbing
matchFileGlob,
matchDirFileGlob,
parseFileGlob,
FileGlob(..),
-- * temp files and dirs
withTempFile,
withTempDirectory,
-- * .faction and .buildinfo files
defaultPackageDesc,
findPackageDesc,
defaultHookedPackageDesc,
findHookedPackageDesc,
-- * reading and writing files safely
withFileContents,
writeFileAtomic,
rewriteFile,
-- * Unicode
fromUTF8,
toUTF8,
readUTF8File,
withUTF8FileContents,
writeUTF8File,
normaliseLineEndings,
-- * generic utils
equating,
comparing,
isInfixOf,
intercalate,
lowercase,
wrapText,
wrapLine,
) where
import Control.Monad
( when, unless, filterM )
#ifdef __GLASGOW_HASKELL__
import Control.Concurrent.MVar
( newEmptyMVar, putMVar, takeMVar )
#endif
import Data.List
( nub, unfoldr, isPrefixOf, tails, intersperse )
import Data.Char as Char
( toLower, chr, ord )
import Data.Bits
( Bits((.|.), (.&.), shiftL, shiftR) )
import System.Directory
( getDirectoryContents, doesDirectoryExist, doesFileExist, removeFile
, findExecutable )
import System.Environment
( getProgName )
import System.Cmd
( rawSystem )
import System.Exit
( exitWith, ExitCode(..) )
import System.FilePath
( normalise, (</>), (<.>), takeDirectory, splitFileName
, splitExtension, splitExtensions, splitDirectories )
import System.Directory
( createDirectory, renameFile, removeDirectoryRecursive )
import System.IO
( Handle, openFile, openBinaryFile, IOMode(ReadMode), hSetBinaryMode
, hGetContents, stderr, stdout, hPutStr, hFlush, hClose )
import System.IO.Error as IO.Error
( isDoesNotExistError, isAlreadyExistsError
, ioeSetFileName, ioeGetFileName, ioeGetErrorString )
#if !(defined(__HUGS__) || (defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ < 608))
import System.IO.Error
( ioeSetLocation, ioeGetLocation )
#endif
import System.IO.Unsafe
( unsafeInterleaveIO )
import qualified Control.Exception as Exception
import Distribution.Text
( display, simpleParse )
import Distribution.Package
( PackageIdentifier )
import Distribution.ModuleName (ModuleName)
import qualified Distribution.ModuleName as ModuleName
import Distribution.Version
(Version(..))
import Control.Exception (evaluate)
import System.Process (runProcess)
#ifdef __GLASGOW_HASKELL__
import Control.Concurrent (forkIO)
import System.Process (runInteractiveProcess, waitForProcess)
#else
import System.Cmd (system)
import System.Directory (getTemporaryDirectory)
#endif
import Distribution.Compat.CopyFile
( copyFile, copyOrdinaryFile, copyExecutableFile
, setFileOrdinary, setFileExecutable, setDirOrdinary )
import Distribution.Compat.TempFile
( openTempFile, openNewBinaryFile, createTempDirectory )
import Distribution.Compat.Exception
( IOException, throwIOIO, tryIO, catchIO, catchExit, onException )
import Distribution.Verbosity
#ifdef VERSION_base
import qualified Paths_libfaction (version)
#endif
-- We only get our own version number when we're building with ourselves
factionVersion :: Version
#if defined(VERSION_base)
factionVersion = Paths_libfaction.version
#elif defined(FACTION_VERSION)
factionVersion = Version [FACTION_VERSION] []
#else
factionVersion = Version [1,9999] [] --used when bootstrapping
#endif
-- ----------------------------------------------------------------------------
-- Exception and logging utils
dieWithLocation :: FilePath -> Maybe Int -> String -> IO a
dieWithLocation filename lineno msg =
ioError . setLocation lineno
. flip ioeSetFileName (normalise filename)
$ userError msg
where
#if defined(__HUGS__) || (defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ < 608)
setLocation _ err = err
#else
setLocation Nothing err = err
setLocation (Just n) err = ioeSetLocation err (show n)
#endif
die :: String -> IO a
die msg = ioError (userError msg)
topHandler :: IO a -> IO a
topHandler prog = catchIO prog handle
where
handle ioe = do
hFlush stdout
pname <- getProgName
hPutStr stderr (mesage pname)
exitWith (ExitFailure 1)
where
mesage pname = wrapText (pname ++ ": " ++ file ++ detail)
file = case ioeGetFileName ioe of
Nothing -> ""
Just path -> path ++ location ++ ": "
#if defined(__HUGS__) || (defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ < 608)
location = ""
#else
location = case ioeGetLocation ioe of
l@(n:_) | n >= '0' && n <= '9' -> ':' : l
_ -> ""
#endif
detail = ioeGetErrorString ioe
-- | Non fatal conditions that may be indicative of an error or problem.
--
-- We display these at the 'normal' verbosity level.
--
warn :: Verbosity -> String -> IO ()
warn verbosity msg =
when (verbosity >= normal) $ do
hFlush stdout
hPutStr stderr (wrapText ("Warning: " ++ msg))
-- | Useful status messages.
--
-- We display these at the 'normal' verbosity level.
--
-- This is for the ordinary helpful status messages that users see. Just
-- enough information to know that things are working but not floods of detail.
--
notice :: Verbosity -> String -> IO ()
notice verbosity msg =
when (verbosity >= normal) $
putStr (wrapText msg)
setupMessage :: Verbosity -> String -> PackageIdentifier -> IO ()
setupMessage verbosity msg pkgid =
notice verbosity (msg ++ ' ': display pkgid ++ "...")
-- | More detail on the operation of some action.
--
-- We display these messages when the verbosity level is 'verbose'
--
info :: Verbosity -> String -> IO ()
info verbosity msg =
when (verbosity >= verbose) $
putStr (wrapText msg)
-- | Detailed internal debugging information
--
-- We display these messages when the verbosity level is 'deafening'
--
debug :: Verbosity -> String -> IO ()
debug verbosity msg =
when (verbosity >= deafening) $ do
putStr (wrapText msg)
hFlush stdout
-- | Perform an IO action, catching any IO exceptions and printing an error
-- if one occurs.
chattyTry :: String -- ^ a description of the action we were attempting
-> IO () -- ^ the action itself
-> IO ()
chattyTry desc action =
catchIO action $ \exception ->
putStrLn $ "Error while " ++ desc ++ ": " ++ show exception
-- -----------------------------------------------------------------------------
-- Helper functions
-- | Wraps text to the default line width. Existing newlines are preserved.
wrapText :: String -> String
wrapText = unlines
. concatMap (map unwords
. wrapLine 79
. words)
. lines
-- | Wraps a list of words to a list of lines of words of a particular width.
wrapLine :: Int -> [String] -> [[String]]
wrapLine width = wrap 0 []
where wrap :: Int -> [String] -> [String] -> [[String]]
wrap 0 [] (w:ws)
| length w + 1 > width
= wrap (length w) [w] ws
wrap col line (w:ws)
| col + length w + 1 > width
= reverse line : wrap 0 [] (w:ws)
wrap col line (w:ws)
= let col' = col + length w + 1
in wrap col' (w:line) ws
wrap _ [] [] = []
wrap _ line [] = [reverse line]
-- -----------------------------------------------------------------------------
-- rawSystem variants
maybeExit :: IO ExitCode -> IO ()
maybeExit cmd = do
res <- cmd
unless (res == ExitSuccess) $ exitWith res
printRawCommandAndArgs :: Verbosity -> FilePath -> [String] -> IO ()
printRawCommandAndArgs verbosity path args
| verbosity >= deafening = print (path, args)
| verbosity >= verbose = putStrLn $ unwords (path : args)
| otherwise = return ()
printRawCommandAndArgsAndEnv :: Verbosity
-> FilePath
-> [String]
-> [(String, String)]
-> IO ()
printRawCommandAndArgsAndEnv verbosity path args env
| verbosity >= deafening = do putStrLn ("Environment: " ++ show env)
print (path, args)
| verbosity >= verbose = putStrLn $ unwords (path : args)
| otherwise = return ()
-- Exit with the same exitcode if the subcommand fails
rawSystemExit :: Verbosity -> FilePath -> [String] -> IO ()
rawSystemExit verbosity path args = do
printRawCommandAndArgs verbosity path args
hFlush stdout
exitcode <- rawSystem path args
unless (exitcode == ExitSuccess) $ do
debug verbosity $ path ++ " returned " ++ show exitcode
exitWith exitcode
rawSystemExitCode :: Verbosity -> FilePath -> [String] -> IO ExitCode
rawSystemExitCode verbosity path args = do
printRawCommandAndArgs verbosity path args
hFlush stdout
exitcode <- rawSystem path args
unless (exitcode == ExitSuccess) $ do
debug verbosity $ path ++ " returned " ++ show exitcode
return exitcode
rawSystemExitWithEnv :: Verbosity
-> FilePath
-> [String]
-> [(String, String)]
-> IO ()
rawSystemExitWithEnv verbosity path args env = do
printRawCommandAndArgsAndEnv verbosity path args env
hFlush stdout
ph <- runProcess path args Nothing (Just env) Nothing Nothing Nothing
exitcode <- waitForProcess ph
unless (exitcode == ExitSuccess) $ do
debug verbosity $ path ++ " returned " ++ show exitcode
exitWith exitcode
-- | Run a command and return its output.
--
-- The output is assumed to be text in the locale encoding.
--
rawSystemStdout :: Verbosity -> FilePath -> [String] -> IO String
rawSystemStdout verbosity path args = do
(output, errors, exitCode) <- rawSystemStdInOut verbosity path args
Nothing False
when (exitCode /= ExitSuccess) $
die errors
return output
-- | Run a command and return its output, errors and exit status. Optionally
-- also supply some input. Also provides control over whether the binary/text
-- mode of the input and output.
--
rawSystemStdInOut :: Verbosity
-> FilePath -> [String]
-> Maybe (String, Bool) -- ^ input text and binary mode
-> Bool -- ^ output in binary mode
-> IO (String, String, ExitCode) -- ^ output, errors, exit
rawSystemStdInOut verbosity path args input outputBinary = do
printRawCommandAndArgs verbosity path args
#ifdef __GLASGOW_HASKELL__
Exception.bracket
(runInteractiveProcess path args Nothing Nothing)
(\(inh,outh,errh,_) -> hClose inh >> hClose outh >> hClose errh)
$ \(inh,outh,errh,pid) -> do
-- output mode depends on what the caller wants
hSetBinaryMode outh outputBinary
-- but the errors are always assumed to be text (in the current locale)
hSetBinaryMode errh False
-- fork off a couple threads to pull on the stderr and stdout
-- so if the process writes to stderr we do not block.
err <- hGetContents errh
out <- hGetContents outh
mv <- newEmptyMVar
let force str = (evaluate (length str) >> return ())
`Exception.finally` putMVar mv ()
--TODO: handle exceptions like text decoding.
_ <- forkIO $ force out
_ <- forkIO $ force err
-- push all the input, if any
case input of
Nothing -> return ()
Just (inputStr, inputBinary) -> do
-- input mode depends on what the caller wants
hSetBinaryMode inh inputBinary
hPutStr inh inputStr
hClose inh
--TODO: this probably fails if the process refuses to consume
-- or if it closes stdin (eg if it exits)
-- wait for both to finish, in either order
takeMVar mv
takeMVar mv
-- wait for the program to terminate
exitcode <- waitForProcess pid
unless (exitcode == ExitSuccess) $
debug verbosity $ path ++ " returned " ++ show exitcode
++ if null err then "" else
" with error message:\n" ++ err
return (out, err, exitcode)
#else
tmpDir <- getTemporaryDirectory
withTempFile tmpDir ".cmd.stdout" $ \outName outHandle ->
withTempFile tmpDir ".cmd.stdin" $ \inName inHandle -> do
hClose outHandle
case input of
Nothing -> return ()
Just (inputStr, inputBinary) -> do
hSetBinaryMode inHandle inputBinary
hPutStr inHandle inputStr
hClose inHandle
let quote name = "'" ++ name ++ "'"
cmd = unwords (map quote (path:args))
++ " <" ++ quote inName
++ " >" ++ quote outName
exitcode <- system cmd
unless (exitcode == ExitSuccess) $
debug verbosity $ path ++ " returned " ++ show exitcode
Exception.bracket (openFile outName ReadMode) hClose $ \hnd -> do
hSetBinaryMode hnd outputBinary
output <- hGetContents hnd
length output `seq` return (output, "", exitcode)
#endif
-- | Look for a program on the path.
findProgramLocation :: Verbosity -> FilePath -> IO (Maybe FilePath)
findProgramLocation verbosity prog = do
debug verbosity $ "searching for " ++ prog ++ " in path."
res <- findExecutable prog
case res of
Nothing -> debug verbosity ("Cannot find " ++ prog ++ " on the path")
Just path -> debug verbosity ("found " ++ prog ++ " at "++ path)
return res
-- | Look for a program and try to find it's version number. It can accept
-- either an absolute path or the name of a program binary, in which case we
-- will look for the program on the path.
--
findProgramVersion :: String -- ^ version args
-> (String -> String) -- ^ function to select version
-- number from program output
-> Verbosity
-> FilePath -- ^ location
-> IO (Maybe Version)
findProgramVersion versionArg selectVersion verbosity path = do
str <- rawSystemStdout verbosity path [versionArg]
`catchIO` (\_ -> return "")
`catchExit` (\_ -> return "")
let version :: Maybe Version
version = simpleParse (selectVersion str)
case version of
Nothing -> warn verbosity $ "cannot determine version of " ++ path
++ " :\n" ++ show str
Just v -> debug verbosity $ path ++ " is version " ++ display v
return version
-- | Like the unix xargs program. Useful for when we've got very long command
-- lines that might overflow an OS limit on command line length and so you
-- need to invoke a command multiple times to get all the args in.
--
-- Use it with either of the rawSystem variants above. For example:
--
-- > xargs (32*1024) (rawSystemExit verbosity) prog fixedArgs bigArgs
--
xargs :: Int -> ([String] -> IO ())
-> [String] -> [String] -> IO ()
xargs maxSize rawSystemFun fixedArgs bigArgs =
let fixedArgSize = sum (map length fixedArgs) + length fixedArgs
chunkSize = maxSize - fixedArgSize
in mapM_ (rawSystemFun . (fixedArgs ++)) (chunks chunkSize bigArgs)
where chunks len = unfoldr $ \s ->
if null s then Nothing
else Just (chunk [] len s)
chunk acc _ [] = (reverse acc,[])
chunk acc len (s:ss)
| len' < len = chunk (s:acc) (len-len'-1) ss
| otherwise = (reverse acc, s:ss)
where len' = length s
-- ------------------------------------------------------------
-- * File Utilities
-- ------------------------------------------------------------
----------------
-- Finding files
-- | Find a file by looking in a search path. The file path must match exactly.
--
findFile :: [FilePath] -- ^search locations
-> FilePath -- ^File Name
-> IO FilePath
findFile searchPath fileName =
findFirstFile id
[ path </> fileName
| path <- nub searchPath]
>>= maybe (die $ fileName ++ " doesn't exist") return
-- | Find a file by looking in a search path with one of a list of possible
-- file extensions. The file base name should be given and it will be tried
-- with each of the extensions in each element of the search path.
--
findFileWithExtension :: [String]
-> [FilePath]
-> FilePath
-> IO (Maybe FilePath)
findFileWithExtension extensions searchPath baseName =
findFirstFile id
[ path </> baseName <.> ext
| path <- nub searchPath
, ext <- nub extensions ]
-- | Like 'findFileWithExtension' but returns which element of the search path
-- the file was found in, and the file path relative to that base directory.
--
findFileWithExtension' :: [String]
-> [FilePath]
-> FilePath
-> IO (Maybe (FilePath, FilePath))
findFileWithExtension' extensions searchPath baseName =
findFirstFile (uncurry (</>))
[ (path, baseName <.> ext)
| path <- nub searchPath
, ext <- nub extensions ]
findFirstFile :: (a -> FilePath) -> [a] -> IO (Maybe a)
findFirstFile file = findFirst
where findFirst [] = return Nothing
findFirst (x:xs) = do exists <- doesFileExist (file x)
if exists
then return (Just x)
else findFirst xs
-- | Finds the files corresponding to a list of Haskell module names.
--
-- As 'findModuleFile' but for a list of module names.
--
findModuleFiles :: [FilePath] -- ^ build prefix (location of objects)
-> [String] -- ^ search suffixes
-> [ModuleName] -- ^ modules
-> IO [(FilePath, FilePath)]
findModuleFiles searchPath extensions moduleNames =
mapM (findModuleFile searchPath extensions) moduleNames
-- | Find the file corresponding to a Haskell module name.
--
-- This is similar to 'findFileWithExtension'' but specialised to a module
-- name. The function fails if the file corresponding to the module is missing.
--
findModuleFile :: [FilePath] -- ^ build prefix (location of objects)
-> [String] -- ^ search suffixes
-> ModuleName -- ^ module
-> IO (FilePath, FilePath)
findModuleFile searchPath extensions moduleName =
maybe notFound return
=<< findFileWithExtension' extensions searchPath
(ModuleName.toFilePath moduleName)
where
notFound = die $ "Error: Could not find module: " ++ display moduleName
++ " with any suffix: " ++ show extensions
++ " in the search path: " ++ show searchPath
-- | List all the files in a directory and all subdirectories.
--
-- The order places files in sub-directories after all the files in their
-- parent directories. The list is generated lazily so is not well defined if
-- the source directory structure changes before the list is used.
--
getDirectoryContentsRecursive :: FilePath -> IO [FilePath]
getDirectoryContentsRecursive topdir = recurseDirectories [""]
where
recurseDirectories :: [FilePath] -> IO [FilePath]
recurseDirectories [] = return []
recurseDirectories (dir:dirs) = unsafeInterleaveIO $ do
(files, dirs') <- collect [] [] =<< getDirectoryContents (topdir </> dir)
files' <- recurseDirectories (dirs' ++ dirs)
return (files ++ files')
where
collect files dirs' [] = return (reverse files, reverse dirs')
collect files dirs' (entry:entries) | ignore entry
= collect files dirs' entries
collect files dirs' (entry:entries) = do
let dirEntry = dir </> entry
isDirectory <- doesDirectoryExist (topdir </> dirEntry)
if isDirectory
then collect files (dirEntry:dirs') entries
else collect (dirEntry:files) dirs' entries
ignore ['.'] = True
ignore ['.', '.'] = True
ignore _ = False
----------------
-- File globbing
data FileGlob
-- | No glob at all, just an ordinary file
= NoGlob FilePath
-- | dir prefix and extension, like @\"foo\/bar\/\*.baz\"@ corresponds to
-- @FileGlob \"foo\/bar\" \".baz\"@
| FileGlob FilePath String
parseFileGlob :: FilePath -> Maybe FileGlob
parseFileGlob filepath = case splitExtensions filepath of
(filepath', ext) -> case splitFileName filepath' of
(dir, "*") | '*' `elem` dir
|| '*' `elem` ext
|| null ext -> Nothing
| null dir -> Just (FileGlob "." ext)
| otherwise -> Just (FileGlob dir ext)
_ | '*' `elem` filepath -> Nothing
| otherwise -> Just (NoGlob filepath)
matchFileGlob :: FilePath -> IO [FilePath]
matchFileGlob = matchDirFileGlob "."
matchDirFileGlob :: FilePath -> FilePath -> IO [FilePath]
matchDirFileGlob dir filepath = case parseFileGlob filepath of
Nothing -> die $ "invalid file glob '" ++ filepath
++ "'. Wildcards '*' are only allowed in place of the file"
++ " name, not in the directory name or file extension."
++ " If a wildcard is used it must be with an file extension."
Just (NoGlob filepath') -> return [filepath']
Just (FileGlob dir' ext) -> do
files <- getDirectoryContents (dir </> dir')
case [ dir' </> file
| file <- files
, let (name, ext') = splitExtensions file
, not (null name) && ext' == ext ] of
[] -> die $ "filepath wildcard '" ++ filepath
++ "' does not match any files."
matches -> return matches
----------------------------------------
-- Copying and installing files and dirs
-- | Same as 'createDirectoryIfMissing' but logs at higher verbosity levels.
--
createDirectoryIfMissingVerbose :: Verbosity
-> Bool -- ^ Create its parents too?
-> FilePath
-> IO ()
createDirectoryIfMissingVerbose verbosity create_parents path0
| create_parents = createDirs (parents path0)
| otherwise = createDirs (take 1 (parents path0))
where
parents = reverse . scanl1 (</>) . splitDirectories . normalise
createDirs [] = return ()
createDirs (dir:[]) = createDir dir throwIOIO
createDirs (dir:dirs) =
createDir dir $ \_ -> do
createDirs dirs
createDir dir throwIOIO
createDir :: FilePath -> (IOException -> IO ()) -> IO ()
createDir dir notExistHandler = do
r <- tryIO $ createDirectoryVerbose verbosity dir
case (r :: Either IOException ()) of
Right () -> return ()
Left e
| isDoesNotExistError e -> notExistHandler e
-- createDirectory (and indeed POSIX mkdir) does not distinguish
-- between a dir already existing and a file already existing. So we
-- check for it here. Unfortunately there is a slight race condition
-- here, but we think it is benign. It could report an exeption in
-- the case that the dir did exist but another process deletes the
-- directory and creates a file in its place before we can check
-- that the directory did indeed exist.
| isAlreadyExistsError e -> (do
isDir <- doesDirectoryExist dir
if isDir then return ()
else throwIOIO e
) `catchIO` ((\_ -> return ()) :: IOException -> IO ())
| otherwise -> throwIOIO e
createDirectoryVerbose :: Verbosity -> FilePath -> IO ()
createDirectoryVerbose verbosity dir = do
info verbosity $ "creating " ++ dir
createDirectory dir
setDirOrdinary dir
-- | Copies a file without copying file permissions. The target file is created
-- with default permissions. Any existing target file is replaced.
--
-- At higher verbosity levels it logs an info message.
--
copyFileVerbose :: Verbosity -> FilePath -> FilePath -> IO ()
copyFileVerbose verbosity src dest = do
info verbosity ("copy " ++ src ++ " to " ++ dest)
copyFile src dest
-- | Install an ordinary file. This is like a file copy but the permissions
-- are set appropriately for an installed file. On Unix it is \"-rw-r--r--\"
-- while on Windows it uses the default permissions for the target directory.
--
installOrdinaryFile :: Verbosity -> FilePath -> FilePath -> IO ()
installOrdinaryFile verbosity src dest = do
info verbosity ("Installing " ++ src ++ " to " ++ dest)
copyOrdinaryFile src dest
-- | Install an executable file. This is like a file copy but the permissions
-- are set appropriately for an installed file. On Unix it is \"-rwxr-xr-x\"
-- while on Windows it uses the default permissions for the target directory.
--
installExecutableFile :: Verbosity -> FilePath -> FilePath -> IO ()
installExecutableFile verbosity src dest = do
info verbosity ("Installing executable " ++ src ++ " to " ++ dest)
copyExecutableFile src dest
-- | Copies a bunch of files to a target directory, preserving the directory
-- structure in the target location. The target directories are created if they
-- do not exist.
--
-- The files are identified by a pair of base directory and a path relative to
-- that base. It is only the relative part that is preserved in the
-- destination.
--
-- For example:
--
-- > copyFiles normal "dist/src"
-- > [("", "src/Foo.hs"), ("dist/build/", "src/Bar.hs")]
--
-- This would copy \"src\/Foo.hs\" to \"dist\/src\/src\/Foo.hs\" and
-- copy \"dist\/build\/src\/Bar.hs\" to \"dist\/src\/src\/Bar.hs\".
--
-- This operation is not atomic. Any IO failure during the copy (including any
-- missing source files) leaves the target in an unknown state so it is best to
-- use it with a freshly created directory so that it can be simply deleted if
-- anything goes wrong.
--
copyFiles :: Verbosity -> FilePath -> [(FilePath, FilePath)] -> IO ()
copyFiles verbosity targetDir srcFiles = do
-- Create parent directories for everything
let dirs = map (targetDir </>) . nub . map (takeDirectory . snd) $ srcFiles
mapM_ (createDirectoryIfMissingVerbose verbosity True) dirs
-- Copy all the files
sequence_ [ let src = srcBase </> srcFile
dest = targetDir </> srcFile
in copyFileVerbose verbosity src dest
| (srcBase, srcFile) <- srcFiles ]
-- | This is like 'copyFiles' but uses 'installOrdinaryFile'.
--
installOrdinaryFiles :: Verbosity -> FilePath -> [(FilePath, FilePath)] -> IO ()
installOrdinaryFiles verbosity targetDir srcFiles = do
-- Create parent directories for everything
let dirs = map (targetDir </>) . nub . map (takeDirectory . snd) $ srcFiles
mapM_ (createDirectoryIfMissingVerbose verbosity True) dirs
-- Copy all the files
sequence_ [ let src = srcBase </> srcFile
dest = targetDir </> srcFile
in installOrdinaryFile verbosity src dest
| (srcBase, srcFile) <- srcFiles ]
-- | This installs all the files in a directory to a target location,
-- preserving the directory layout. All the files are assumed to be ordinary
-- rather than executable files.
--
installDirectoryContents :: Verbosity -> FilePath -> FilePath -> IO ()
installDirectoryContents verbosity srcDir destDir = do
info verbosity ("copy directory '" ++ srcDir ++ "' to '" ++ destDir ++ "'.")
srcFiles <- getDirectoryContentsRecursive srcDir
installOrdinaryFiles verbosity destDir [ (srcDir, f) | f <- srcFiles ]
---------------------------------
-- Deprecated file copy functions
{-# DEPRECATED smartCopySources
"Use findModuleFiles and copyFiles or installOrdinaryFiles" #-}
smartCopySources :: Verbosity -> [FilePath] -> FilePath
-> [ModuleName] -> [String] -> IO ()
smartCopySources verbosity searchPath targetDir moduleNames extensions =
findModuleFiles searchPath extensions moduleNames
>>= copyFiles verbosity targetDir
{-# DEPRECATED copyDirectoryRecursiveVerbose
"You probably want installDirectoryContents instead" #-}
copyDirectoryRecursiveVerbose :: Verbosity -> FilePath -> FilePath -> IO ()
copyDirectoryRecursiveVerbose verbosity srcDir destDir = do
info verbosity ("copy directory '" ++ srcDir ++ "' to '" ++ destDir ++ "'.")
srcFiles <- getDirectoryContentsRecursive srcDir
copyFiles verbosity destDir [ (srcDir, f) | f <- srcFiles ]
---------------------------
-- Temporary files and dirs
-- | Use a temporary filename that doesn't already exist.
--
withTempFile :: FilePath -- ^ Temp dir to create the file in
-> String -- ^ File name template. See 'openTempFile'.
-> (FilePath -> Handle -> IO a) -> IO a
withTempFile tmpDir template action =
Exception.bracket
(openTempFile tmpDir template)
(\(name, handle) -> hClose handle >> removeFile name)
(uncurry action)
-- | Create and use a temporary directory.
--
-- Creates a new temporary directory inside the given directory, making use
-- of the template. The temp directory is deleted after use. For example:
--
-- > withTempDirectory verbosity "src" "sdist." $ \tmpDir -> do ...
--
-- The @tmpDir@ will be a new subdirectory of the given directory, e.g.
-- @src/sdist.342@.
--
withTempDirectory :: Verbosity -> FilePath -> String -> (FilePath -> IO a) -> IO a
withTempDirectory _verbosity targetDir template =
Exception.bracket
(createTempDirectory targetDir template)
(removeDirectoryRecursive)
-----------------------------------
-- Safely reading and writing files
-- | Gets the contents of a file, but guarantee that it gets closed.
--
-- The file is read lazily but if it is not fully consumed by the action then
-- the remaining input is truncated and the file is closed.
--
withFileContents :: FilePath -> (String -> IO a) -> IO a
withFileContents name action =
Exception.bracket (openFile name ReadMode) hClose
(\hnd -> hGetContents hnd >>= action)
-- | Writes a file atomically.
--
-- The file is either written sucessfully or an IO exception is raised and
-- the original file is left unchanged.
--
-- On windows it is not possible to delete a file that is open by a process.
-- This case will give an IO exception but the atomic property is not affected.
--
writeFileAtomic :: FilePath -> String -> IO ()
writeFileAtomic targetFile content = do
(tmpFile, tmpHandle) <- openNewBinaryFile targetDir template
do hPutStr tmpHandle content
hClose tmpHandle
renameFile tmpFile targetFile
`onException` do hClose tmpHandle
removeFile tmpFile
where
template = targetName <.> "tmp"
targetDir | null targetDir_ = currentDir
| otherwise = targetDir_
--TODO: remove this when takeDirectory/splitFileName is fixed
-- to always return a valid dir
(targetDir_,targetName) = splitFileName targetFile
-- | Write a file but only if it would have new content. If we would be writing
-- the same as the existing content then leave the file as is so that we do not
-- update the file's modification time.
--
rewriteFile :: FilePath -> String -> IO ()
rewriteFile path newContent =
flip catchIO mightNotExist $ do
existingContent <- readFile path
_ <- evaluate (length existingContent)
unless (existingContent == newContent) $
writeFileAtomic path newContent
where
mightNotExist e | isDoesNotExistError e = writeFileAtomic path newContent
| otherwise = ioError e
-- | The path name that represents the current directory.
-- In Unix, it's @\".\"@, but this is system-specific.
-- (E.g. AmigaOS uses the empty string @\"\"@ for the current directory.)
currentDir :: FilePath
currentDir = "."
-- ------------------------------------------------------------
-- * Finding the description file
-- ------------------------------------------------------------
-- |Package description file (/pkgname/@.faction@)
defaultPackageDesc :: Verbosity -> IO FilePath
defaultPackageDesc _verbosity = findPackageDesc currentDir
-- |Find a package description file in the given directory. Looks for
-- @.faction@ files.
findPackageDesc :: FilePath -- ^Where to look
-> IO FilePath -- ^<pkgname>.faction
findPackageDesc dir
= do files <- getDirectoryContents dir
-- to make sure we do not mistake a ~/.faction/ dir for
-- a <pkgname>.faction file we filter to exclude dirs and null
-- base file names:
factionFiles <- filterM doesFileExist
[ dir </> file
| file <- files
, let (name, ext) = splitExtension file
, not (null name) && ext == ".faction" ]
case factionFiles of
[] -> noDesc
[factionFile] -> return factionFile
multiple -> multiDesc multiple
where
noDesc :: IO a
noDesc = die $ "No faction file found.\n"
++ "Please create a package description file <pkgname>.faction"
multiDesc :: [String] -> IO a
multiDesc l = die $ "Multiple faction files found.\n"
++ "Please use only one of: "
++ intercalate ", " l
-- |Optional auxiliary package information file (/pkgname/@.buildinfo@)
defaultHookedPackageDesc :: IO (Maybe FilePath)
defaultHookedPackageDesc = findHookedPackageDesc currentDir
-- |Find auxiliary package information in the given directory.
-- Looks for @.buildinfo@ files.
findHookedPackageDesc
:: FilePath -- ^Directory to search
-> IO (Maybe FilePath) -- ^/dir/@\/@/pkgname/@.buildinfo@, if present
findHookedPackageDesc dir = do
files <- getDirectoryContents dir
buildInfoFiles <- filterM doesFileExist
[ dir </> file
| file <- files
, let (name, ext) = splitExtension file
, not (null name) && ext == buildInfoExt ]
case buildInfoFiles of
[] -> return Nothing
[f] -> return (Just f)
_ -> die ("Multiple files with extension " ++ buildInfoExt)
buildInfoExt :: String
buildInfoExt = ".buildinfo"
-- ------------------------------------------------------------
-- * Unicode stuff
-- ------------------------------------------------------------
-- This is a modification of the UTF8 code from gtk2hs and the
-- utf8-string package.
fromUTF8 :: String -> String
fromUTF8 [] = []
fromUTF8 (c:cs)
| c <= '\x7F' = c : fromUTF8 cs
| c <= '\xBF' = replacementChar : fromUTF8 cs
| c <= '\xDF' = twoBytes c cs
| c <= '\xEF' = moreBytes 3 0x800 cs (ord c .&. 0xF)
| c <= '\xF7' = moreBytes 4 0x10000 cs (ord c .&. 0x7)
| c <= '\xFB' = moreBytes 5 0x200000 cs (ord c .&. 0x3)
| c <= '\xFD' = moreBytes 6 0x4000000 cs (ord c .&. 0x1)
| otherwise = replacementChar : fromUTF8 cs
where
twoBytes c0 (c1:cs')
| ord c1 .&. 0xC0 == 0x80
= let d = ((ord c0 .&. 0x1F) `shiftL` 6)
.|. (ord c1 .&. 0x3F)
in if d >= 0x80
then chr d : fromUTF8 cs'
else replacementChar : fromUTF8 cs'
twoBytes _ cs' = replacementChar : fromUTF8 cs'
moreBytes :: Int -> Int -> [Char] -> Int -> [Char]
moreBytes 1 overlong cs' acc
| overlong <= acc && acc <= 0x10FFFF
&& (acc < 0xD800 || 0xDFFF < acc)
&& (acc < 0xFFFE || 0xFFFF < acc)
= chr acc : fromUTF8 cs'
| otherwise
= replacementChar : fromUTF8 cs'
moreBytes byteCount overlong (cn:cs') acc
| ord cn .&. 0xC0 == 0x80
= moreBytes (byteCount-1) overlong cs'
((acc `shiftL` 6) .|. ord cn .&. 0x3F)
moreBytes _ _ cs' _
= replacementChar : fromUTF8 cs'
replacementChar = '\xfffd'
toUTF8 :: String -> String
toUTF8 [] = []
toUTF8 (c:cs)
| c <= '\x07F' = c
: toUTF8 cs
| c <= '\x7FF' = chr (0xC0 .|. (w `shiftR` 6))
: chr (0x80 .|. (w .&. 0x3F))
: toUTF8 cs
| c <= '\xFFFF'= chr (0xE0 .|. (w `shiftR` 12))
: chr (0x80 .|. ((w `shiftR` 6) .&. 0x3F))
: chr (0x80 .|. (w .&. 0x3F))
: toUTF8 cs
| otherwise = chr (0xf0 .|. (w `shiftR` 18))
: chr (0x80 .|. ((w `shiftR` 12) .&. 0x3F))
: chr (0x80 .|. ((w `shiftR` 6) .&. 0x3F))
: chr (0x80 .|. (w .&. 0x3F))
: toUTF8 cs
where w = ord c
-- | Ignore a Unicode byte order mark (BOM) at the beginning of the input
--
ignoreBOM :: String -> String
ignoreBOM ('\xFEFF':string) = string
ignoreBOM string = string
-- | Reads a UTF8 encoded text file as a Unicode String
--
-- Reads lazily using ordinary 'readFile'.
--
readUTF8File :: FilePath -> IO String
readUTF8File f = fmap (ignoreBOM . fromUTF8)
. hGetContents =<< openBinaryFile f ReadMode
-- | Reads a UTF8 encoded text file as a Unicode String
--
-- Same behaviour as 'withFileContents'.
--
withUTF8FileContents :: FilePath -> (String -> IO a) -> IO a
withUTF8FileContents name action =
Exception.bracket
(openBinaryFile name ReadMode)
hClose
(\hnd -> hGetContents hnd >>= action . ignoreBOM . fromUTF8)
-- | Writes a Unicode String as a UTF8 encoded text file.
--
-- Uses 'writeFileAtomic', so provides the same guarantees.
--
writeUTF8File :: FilePath -> String -> IO ()
writeUTF8File path = writeFileAtomic path . toUTF8
-- | Fix different systems silly line ending conventions
normaliseLineEndings :: String -> String
normaliseLineEndings [] = []
normaliseLineEndings ('\r':'\n':s) = '\n' : normaliseLineEndings s -- windows
normaliseLineEndings ('\r':s) = '\n' : normaliseLineEndings s -- old osx
normaliseLineEndings ( c :s) = c : normaliseLineEndings s
-- ------------------------------------------------------------
-- * Common utils
-- ------------------------------------------------------------
equating :: Eq a => (b -> a) -> b -> b -> Bool
equating p x y = p x == p y
comparing :: Ord a => (b -> a) -> b -> b -> Ordering
comparing p x y = p x `compare` p y
isInfixOf :: String -> String -> Bool
isInfixOf needle haystack = any (isPrefixOf needle) (tails haystack)
intercalate :: [a] -> [[a]] -> [a]
intercalate sep = concat . intersperse sep
lowercase :: String -> String
lowercase = map Char.toLower
| IreneKnapp/Faction | libfaction/Distribution/Simple/Utils.hs | Haskell | bsd-3-clause | 40,229 |
{-# LANGUAGE TypeOperators, TupleSections #-}
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
{-# OPTIONS_GHC -Wall #-}
----------------------------------------------------------------------
-- |
-- Module : Data.StateTrie
-- Copyright : (c) Conal Elliott 2012
-- License : BSD3
--
-- Maintainer : [email protected]
-- Stability : experimental
--
-- Memoizing State monad
----------------------------------------------------------------------
module Data.StateTrie
( StateTrieX, StateTrie(..)
, toState, fromState
, get, put, runStateTrie, evalStateTrie, execStateTrie
,
) where
import Control.Arrow (first)
import Control.Applicative (Applicative(..))
import Control.Monad.State -- mtl
import FunctorCombo.StrictMemo (HasTrie(..),(:->:))
-- | 'StateTrie' inner representation
type StateTrieX s a = s :->: (a,s)
-- | Memoizing state monad
newtype StateTrie s a = StateTrie { unStateTrie :: StateTrieX s a }
-- | Operate inside a 'StateTrie'.
inStateTrie :: (StateTrieX s a -> StateTrieX t b)
-> (StateTrie s a -> StateTrie t b)
inStateTrie = StateTrie <~ unStateTrie
{- unused
inStateTrie2 :: (StateTrieX s a -> StateTrieX t b -> StateTrieX u c)
-> (StateTrie s a -> StateTrie t b -> StateTrie u c)
inStateTrie2 = inStateTrie <~ unStateTrie
-}
-- | Run a memoized stateful computation
runStateTrie :: HasTrie s => StateTrie s a -> s -> (a,s)
runStateTrie (StateTrie t) = untrie t
-- | Run a memoized stateful computation and return just value
evalStateTrie :: HasTrie s => StateTrie s a -> s -> a
evalStateTrie = (result.result) fst runStateTrie
-- | Run a memoized stateful computation and return just state
execStateTrie :: HasTrie s => StateTrie s a -> s -> s
execStateTrie = (result.result) snd runStateTrie
instance HasTrie s => Functor (StateTrie s) where
fmap = inStateTrie . fmap . first
instance HasTrie s => Applicative (StateTrie s) where
pure a = StateTrie (trie (a,))
(<*>) = inState2 (<*>)
-- | 'State'-to-'StateTrie' adapter
fromState :: HasTrie s => State s a -> StateTrie s a
fromState = StateTrie . trie . runState
-- | 'StateTrie'-to-'State' adapter
toState :: HasTrie s => StateTrie s a -> State s a
toState = state . untrie . unStateTrie
-- | Transform using 'State' view
inState :: (HasTrie s, HasTrie t) =>
(State s a -> State t b)
-> (StateTrie s a -> StateTrie t b)
inState = fromState <~ toState
-- | Transform using 'State' view
inState2 :: (HasTrie s, HasTrie t, HasTrie u) =>
(State s a -> State t b -> State u c)
-> (StateTrie s a -> StateTrie t b -> StateTrie u c)
inState2 = inState <~ toState
instance HasTrie s => Monad (StateTrie s) where
return = pure
m >>= f = joinST (fmap f m)
joinST :: HasTrie s => StateTrie s (StateTrie s a) -> StateTrie s a
joinST = fromState . join . fmap toState . toState
-- joinST = inState (join . fmap toState)
-- = inState ((=<<) toState)
instance HasTrie s => MonadState s (StateTrie s) where
state = StateTrie . trie
-- TODO: Perhaps use 'state' in the definitions of pure and fromState.
{--------------------------------------------------------------------
Misc
--------------------------------------------------------------------}
-- | Add post- & pre-processing
(<~) :: (b -> b') -> (a' -> a) -> ((a -> b) -> (a' -> b'))
(h <~ f) g = h . g . f
-- | Add post-processing
result :: (b -> b') -> ((a -> b) -> (a -> b'))
result = (.)
-- result = (<~ id)
| conal/state-trie | src/Data/StateTrie.hs | Haskell | bsd-3-clause | 3,506 |
module Test.OCanrenize where
import OCanrenize
import Test.Helper (test)
import Syntax
unit_OCanrenizeTerm = do
test ocanren (C "fst" [] :: Term X) "(fst_ ())"
test ocanren (C "snd" [] :: Term X) "(snd_ ())"
test ocanren (C "fill" [] :: Term X) "(fill ())" | kajigor/uKanren_transformations | test/auto/Test/OCanrenize.hs | Haskell | bsd-3-clause | 270 |
-----------------------------------------------------------------------------
--
-- The register liveness determinator
--
-- (c) The University of Glasgow 2004
--
-----------------------------------------------------------------------------
{-# OPTIONS -Wall -fno-warn-name-shadowing #-}
module RegAlloc.Liveness (
RegSet,
RegMap, emptyRegMap,
BlockMap, emptyBlockMap,
LiveCmmDecl,
InstrSR (..),
LiveInstr (..),
Liveness (..),
LiveInfo (..),
LiveBasicBlock,
mapBlockTop, mapBlockTopM, mapSCCM,
mapGenBlockTop, mapGenBlockTopM,
stripLive,
stripLiveBlock,
slurpConflicts,
slurpReloadCoalesce,
eraseDeltasLive,
patchEraseLive,
patchRegsLiveInstr,
reverseBlocksInTops,
regLiveness,
natCmmTopToLive
) where
import Reg
import Instruction
import BlockId
import OldCmm hiding (RegSet)
import OldPprCmm()
import Digraph
import Outputable
import Platform
import Unique
import UniqSet
import UniqFM
import UniqSupply
import Bag
import State
import FastString
import Data.List
import Data.Maybe
import Data.Map (Map)
import Data.Set (Set)
import qualified Data.Map as Map
-----------------------------------------------------------------------------
type RegSet = UniqSet Reg
type RegMap a = UniqFM a
emptyRegMap :: UniqFM a
emptyRegMap = emptyUFM
type BlockMap a = BlockEnv a
-- | A top level thing which carries liveness information.
type LiveCmmDecl statics instr
= GenCmmDecl
statics
LiveInfo
[SCC (LiveBasicBlock instr)]
-- | The register allocator also wants to use SPILL/RELOAD meta instructions,
-- so we'll keep those here.
data InstrSR instr
-- | A real machine instruction
= Instr instr
-- | spill this reg to a stack slot
| SPILL Reg Int
-- | reload this reg from a stack slot
| RELOAD Int Reg
instance Instruction instr => Instruction (InstrSR instr) where
regUsageOfInstr i
= case i of
Instr instr -> regUsageOfInstr instr
SPILL reg _ -> RU [reg] []
RELOAD _ reg -> RU [] [reg]
patchRegsOfInstr i f
= case i of
Instr instr -> Instr (patchRegsOfInstr instr f)
SPILL reg slot -> SPILL (f reg) slot
RELOAD slot reg -> RELOAD slot (f reg)
isJumpishInstr i
= case i of
Instr instr -> isJumpishInstr instr
_ -> False
jumpDestsOfInstr i
= case i of
Instr instr -> jumpDestsOfInstr instr
_ -> []
patchJumpInstr i f
= case i of
Instr instr -> Instr (patchJumpInstr instr f)
_ -> i
mkSpillInstr = error "mkSpillInstr[InstrSR]: Not making SPILL meta-instr"
mkLoadInstr = error "mkLoadInstr[InstrSR]: Not making LOAD meta-instr"
takeDeltaInstr i
= case i of
Instr instr -> takeDeltaInstr instr
_ -> Nothing
isMetaInstr i
= case i of
Instr instr -> isMetaInstr instr
_ -> False
mkRegRegMoveInstr platform r1 r2
= Instr (mkRegRegMoveInstr platform r1 r2)
takeRegRegMoveInstr i
= case i of
Instr instr -> takeRegRegMoveInstr instr
_ -> Nothing
mkJumpInstr target = map Instr (mkJumpInstr target)
-- | An instruction with liveness information.
data LiveInstr instr
= LiveInstr (InstrSR instr) (Maybe Liveness)
-- | Liveness information.
-- The regs which die are ones which are no longer live in the *next* instruction
-- in this sequence.
-- (NB. if the instruction is a jump, these registers might still be live
-- at the jump target(s) - you have to check the liveness at the destination
-- block to find out).
data Liveness
= Liveness
{ liveBorn :: RegSet -- ^ registers born in this instruction (written to for first time).
, liveDieRead :: RegSet -- ^ registers that died because they were read for the last time.
, liveDieWrite :: RegSet } -- ^ registers that died because they were clobbered by something.
-- | Stash regs live on entry to each basic block in the info part of the cmm code.
data LiveInfo
= LiveInfo
(Maybe CmmStatics) -- cmm info table static stuff
(Maybe BlockId) -- id of the first block
(Maybe (BlockMap RegSet)) -- argument locals live on entry to this block
(Map BlockId (Set Int)) -- stack slots live on entry to this block
-- | A basic block with liveness information.
type LiveBasicBlock instr
= GenBasicBlock (LiveInstr instr)
instance PlatformOutputable instr
=> PlatformOutputable (InstrSR instr) where
pprPlatform platform (Instr realInstr)
= pprPlatform platform realInstr
pprPlatform _ (SPILL reg slot)
= hcat [
ptext (sLit "\tSPILL"),
char ' ',
ppr reg,
comma,
ptext (sLit "SLOT") <> parens (int slot)]
pprPlatform _ (RELOAD slot reg)
= hcat [
ptext (sLit "\tRELOAD"),
char ' ',
ptext (sLit "SLOT") <> parens (int slot),
comma,
ppr reg]
instance PlatformOutputable instr
=> PlatformOutputable (LiveInstr instr) where
pprPlatform platform (LiveInstr instr Nothing)
= pprPlatform platform instr
pprPlatform platform (LiveInstr instr (Just live))
= pprPlatform platform instr
$$ (nest 8
$ vcat
[ pprRegs (ptext (sLit "# born: ")) (liveBorn live)
, pprRegs (ptext (sLit "# r_dying: ")) (liveDieRead live)
, pprRegs (ptext (sLit "# w_dying: ")) (liveDieWrite live) ]
$+$ space)
where pprRegs :: SDoc -> RegSet -> SDoc
pprRegs name regs
| isEmptyUniqSet regs = empty
| otherwise = name <> (hcat $ punctuate space $ map ppr $ uniqSetToList regs)
instance PlatformOutputable LiveInfo where
pprPlatform platform (LiveInfo mb_static firstId liveVRegsOnEntry liveSlotsOnEntry)
= (maybe empty (pprPlatform platform) mb_static)
$$ text "# firstId = " <> ppr firstId
$$ text "# liveVRegsOnEntry = " <> ppr liveVRegsOnEntry
$$ text "# liveSlotsOnEntry = " <> text (show liveSlotsOnEntry)
-- | map a function across all the basic blocks in this code
--
mapBlockTop
:: (LiveBasicBlock instr -> LiveBasicBlock instr)
-> LiveCmmDecl statics instr -> LiveCmmDecl statics instr
mapBlockTop f cmm
= evalState (mapBlockTopM (\x -> return $ f x) cmm) ()
-- | map a function across all the basic blocks in this code (monadic version)
--
mapBlockTopM
:: Monad m
=> (LiveBasicBlock instr -> m (LiveBasicBlock instr))
-> LiveCmmDecl statics instr -> m (LiveCmmDecl statics instr)
mapBlockTopM _ cmm@(CmmData{})
= return cmm
mapBlockTopM f (CmmProc header label sccs)
= do sccs' <- mapM (mapSCCM f) sccs
return $ CmmProc header label sccs'
mapSCCM :: Monad m => (a -> m b) -> SCC a -> m (SCC b)
mapSCCM f (AcyclicSCC x)
= do x' <- f x
return $ AcyclicSCC x'
mapSCCM f (CyclicSCC xs)
= do xs' <- mapM f xs
return $ CyclicSCC xs'
-- map a function across all the basic blocks in this code
mapGenBlockTop
:: (GenBasicBlock i -> GenBasicBlock i)
-> (GenCmmDecl d h (ListGraph i) -> GenCmmDecl d h (ListGraph i))
mapGenBlockTop f cmm
= evalState (mapGenBlockTopM (\x -> return $ f x) cmm) ()
-- | map a function across all the basic blocks in this code (monadic version)
mapGenBlockTopM
:: Monad m
=> (GenBasicBlock i -> m (GenBasicBlock i))
-> (GenCmmDecl d h (ListGraph i) -> m (GenCmmDecl d h (ListGraph i)))
mapGenBlockTopM _ cmm@(CmmData{})
= return cmm
mapGenBlockTopM f (CmmProc header label (ListGraph blocks))
= do blocks' <- mapM f blocks
return $ CmmProc header label (ListGraph blocks')
-- | Slurp out the list of register conflicts and reg-reg moves from this top level thing.
-- Slurping of conflicts and moves is wrapped up together so we don't have
-- to make two passes over the same code when we want to build the graph.
--
slurpConflicts
:: Instruction instr
=> LiveCmmDecl statics instr
-> (Bag (UniqSet Reg), Bag (Reg, Reg))
slurpConflicts live
= slurpCmm (emptyBag, emptyBag) live
where slurpCmm rs CmmData{} = rs
slurpCmm rs (CmmProc info _ sccs)
= foldl' (slurpSCC info) rs sccs
slurpSCC info rs (AcyclicSCC b)
= slurpBlock info rs b
slurpSCC info rs (CyclicSCC bs)
= foldl' (slurpBlock info) rs bs
slurpBlock info rs (BasicBlock blockId instrs)
| LiveInfo _ _ (Just blockLive) _ <- info
, Just rsLiveEntry <- mapLookup blockId blockLive
, (conflicts, moves) <- slurpLIs rsLiveEntry rs instrs
= (consBag rsLiveEntry conflicts, moves)
| otherwise
= panic "Liveness.slurpConflicts: bad block"
slurpLIs rsLive (conflicts, moves) []
= (consBag rsLive conflicts, moves)
slurpLIs rsLive rs (LiveInstr _ Nothing : lis)
= slurpLIs rsLive rs lis
slurpLIs rsLiveEntry (conflicts, moves) (LiveInstr instr (Just live) : lis)
= let
-- regs that die because they are read for the last time at the start of an instruction
-- are not live across it.
rsLiveAcross = rsLiveEntry `minusUniqSet` (liveDieRead live)
-- regs live on entry to the next instruction.
-- be careful of orphans, make sure to delete dying regs _after_ unioning
-- in the ones that are born here.
rsLiveNext = (rsLiveAcross `unionUniqSets` (liveBorn live))
`minusUniqSet` (liveDieWrite live)
-- orphan vregs are the ones that die in the same instruction they are born in.
-- these are likely to be results that are never used, but we still
-- need to assign a hreg to them..
rsOrphans = intersectUniqSets
(liveBorn live)
(unionUniqSets (liveDieWrite live) (liveDieRead live))
--
rsConflicts = unionUniqSets rsLiveNext rsOrphans
in case takeRegRegMoveInstr instr of
Just rr -> slurpLIs rsLiveNext
( consBag rsConflicts conflicts
, consBag rr moves) lis
Nothing -> slurpLIs rsLiveNext
( consBag rsConflicts conflicts
, moves) lis
-- | For spill\/reloads
--
-- SPILL v1, slot1
-- ...
-- RELOAD slot1, v2
--
-- If we can arrange that v1 and v2 are allocated to the same hreg it's more likely
-- the spill\/reload instrs can be cleaned and replaced by a nop reg-reg move.
--
--
slurpReloadCoalesce
:: forall statics instr. Instruction instr
=> LiveCmmDecl statics instr
-> Bag (Reg, Reg)
slurpReloadCoalesce live
= slurpCmm emptyBag live
where
slurpCmm :: Bag (Reg, Reg)
-> GenCmmDecl t t1 [SCC (LiveBasicBlock instr)]
-> Bag (Reg, Reg)
slurpCmm cs CmmData{} = cs
slurpCmm cs (CmmProc _ _ sccs)
= slurpComp cs (flattenSCCs sccs)
slurpComp :: Bag (Reg, Reg)
-> [LiveBasicBlock instr]
-> Bag (Reg, Reg)
slurpComp cs blocks
= let (moveBags, _) = runState (slurpCompM blocks) emptyUFM
in unionManyBags (cs : moveBags)
slurpCompM :: [LiveBasicBlock instr]
-> State (UniqFM [UniqFM Reg]) [Bag (Reg, Reg)]
slurpCompM blocks
= do -- run the analysis once to record the mapping across jumps.
mapM_ (slurpBlock False) blocks
-- run it a second time while using the information from the last pass.
-- We /could/ run this many more times to deal with graphical control
-- flow and propagating info across multiple jumps, but it's probably
-- not worth the trouble.
mapM (slurpBlock True) blocks
slurpBlock :: Bool -> LiveBasicBlock instr
-> State (UniqFM [UniqFM Reg]) (Bag (Reg, Reg))
slurpBlock propagate (BasicBlock blockId instrs)
= do -- grab the slot map for entry to this block
slotMap <- if propagate
then getSlotMap blockId
else return emptyUFM
(_, mMoves) <- mapAccumLM slurpLI slotMap instrs
return $ listToBag $ catMaybes mMoves
slurpLI :: UniqFM Reg -- current slotMap
-> LiveInstr instr
-> State (UniqFM [UniqFM Reg]) -- blockId -> [slot -> reg]
-- for tracking slotMaps across jumps
( UniqFM Reg -- new slotMap
, Maybe (Reg, Reg)) -- maybe a new coalesce edge
slurpLI slotMap li
-- remember what reg was stored into the slot
| LiveInstr (SPILL reg slot) _ <- li
, slotMap' <- addToUFM slotMap slot reg
= return (slotMap', Nothing)
-- add an edge betwen the this reg and the last one stored into the slot
| LiveInstr (RELOAD slot reg) _ <- li
= case lookupUFM slotMap slot of
Just reg2
| reg /= reg2 -> return (slotMap, Just (reg, reg2))
| otherwise -> return (slotMap, Nothing)
Nothing -> return (slotMap, Nothing)
-- if we hit a jump, remember the current slotMap
| LiveInstr (Instr instr) _ <- li
, targets <- jumpDestsOfInstr instr
, not $ null targets
= do mapM_ (accSlotMap slotMap) targets
return (slotMap, Nothing)
| otherwise
= return (slotMap, Nothing)
-- record a slotmap for an in edge to this block
accSlotMap slotMap blockId
= modify (\s -> addToUFM_C (++) s blockId [slotMap])
-- work out the slot map on entry to this block
-- if we have slot maps for multiple in-edges then we need to merge them.
getSlotMap blockId
= do map <- get
let slotMaps = fromMaybe [] (lookupUFM map blockId)
return $ foldr mergeSlotMaps emptyUFM slotMaps
mergeSlotMaps :: UniqFM Reg -> UniqFM Reg -> UniqFM Reg
mergeSlotMaps map1 map2
= listToUFM
$ [ (k, r1) | (k, r1) <- ufmToList map1
, case lookupUFM map2 k of
Nothing -> False
Just r2 -> r1 == r2 ]
-- | Strip away liveness information, yielding NatCmmDecl
stripLive
:: (PlatformOutputable statics,
PlatformOutputable instr,
Instruction instr)
=> Platform
-> LiveCmmDecl statics instr
-> NatCmmDecl statics instr
stripLive platform live
= stripCmm live
where stripCmm :: (PlatformOutputable statics,
PlatformOutputable instr,
Instruction instr)
=> LiveCmmDecl statics instr -> NatCmmDecl statics instr
stripCmm (CmmData sec ds) = CmmData sec ds
stripCmm (CmmProc (LiveInfo info (Just first_id) _ _) label sccs)
= let final_blocks = flattenSCCs sccs
-- make sure the block that was first in the input list
-- stays at the front of the output. This is the entry point
-- of the proc, and it needs to come first.
((first':_), rest')
= partition ((== first_id) . blockId) final_blocks
in CmmProc info label
(ListGraph $ map (stripLiveBlock platform) $ first' : rest')
-- procs used for stg_split_markers don't contain any blocks, and have no first_id.
stripCmm (CmmProc (LiveInfo info Nothing _ _) label [])
= CmmProc info label (ListGraph [])
-- If the proc has blocks but we don't know what the first one was, then we're dead.
stripCmm proc
= pprPanic "RegAlloc.Liveness.stripLive: no first_id on proc" (pprPlatform platform proc)
-- | Strip away liveness information from a basic block,
-- and make real spill instructions out of SPILL, RELOAD pseudos along the way.
stripLiveBlock
:: Instruction instr
=> Platform
-> LiveBasicBlock instr
-> NatBasicBlock instr
stripLiveBlock platform (BasicBlock i lis)
= BasicBlock i instrs'
where (instrs', _)
= runState (spillNat [] lis) 0
spillNat acc []
= return (reverse acc)
spillNat acc (LiveInstr (SPILL reg slot) _ : instrs)
= do delta <- get
spillNat (mkSpillInstr platform reg delta slot : acc) instrs
spillNat acc (LiveInstr (RELOAD slot reg) _ : instrs)
= do delta <- get
spillNat (mkLoadInstr platform reg delta slot : acc) instrs
spillNat acc (LiveInstr (Instr instr) _ : instrs)
| Just i <- takeDeltaInstr instr
= do put i
spillNat acc instrs
spillNat acc (LiveInstr (Instr instr) _ : instrs)
= spillNat (instr : acc) instrs
-- | Erase Delta instructions.
eraseDeltasLive
:: Instruction instr
=> LiveCmmDecl statics instr
-> LiveCmmDecl statics instr
eraseDeltasLive cmm
= mapBlockTop eraseBlock cmm
where
eraseBlock (BasicBlock id lis)
= BasicBlock id
$ filter (\(LiveInstr i _) -> not $ isJust $ takeDeltaInstr i)
$ lis
-- | Patch the registers in this code according to this register mapping.
-- also erase reg -> reg moves when the reg is the same.
-- also erase reg -> reg moves when the destination dies in this instr.
patchEraseLive
:: Instruction instr
=> (Reg -> Reg)
-> LiveCmmDecl statics instr -> LiveCmmDecl statics instr
patchEraseLive patchF cmm
= patchCmm cmm
where
patchCmm cmm@CmmData{} = cmm
patchCmm (CmmProc info label sccs)
| LiveInfo static id (Just blockMap) mLiveSlots <- info
= let
patchRegSet set = mkUniqSet $ map patchF $ uniqSetToList set
blockMap' = mapMap patchRegSet blockMap
info' = LiveInfo static id (Just blockMap') mLiveSlots
in CmmProc info' label $ map patchSCC sccs
| otherwise
= panic "RegAlloc.Liveness.patchEraseLive: no blockMap"
patchSCC (AcyclicSCC b) = AcyclicSCC (patchBlock b)
patchSCC (CyclicSCC bs) = CyclicSCC (map patchBlock bs)
patchBlock (BasicBlock id lis)
= BasicBlock id $ patchInstrs lis
patchInstrs [] = []
patchInstrs (li : lis)
| LiveInstr i (Just live) <- li'
, Just (r1, r2) <- takeRegRegMoveInstr i
, eatMe r1 r2 live
= patchInstrs lis
| otherwise
= li' : patchInstrs lis
where li' = patchRegsLiveInstr patchF li
eatMe r1 r2 live
-- source and destination regs are the same
| r1 == r2 = True
-- desination reg is never used
| elementOfUniqSet r2 (liveBorn live)
, elementOfUniqSet r2 (liveDieRead live) || elementOfUniqSet r2 (liveDieWrite live)
= True
| otherwise = False
-- | Patch registers in this LiveInstr, including the liveness information.
--
patchRegsLiveInstr
:: Instruction instr
=> (Reg -> Reg)
-> LiveInstr instr -> LiveInstr instr
patchRegsLiveInstr patchF li
= case li of
LiveInstr instr Nothing
-> LiveInstr (patchRegsOfInstr instr patchF) Nothing
LiveInstr instr (Just live)
-> LiveInstr
(patchRegsOfInstr instr patchF)
(Just live
{ -- WARNING: have to go via lists here because patchF changes the uniq in the Reg
liveBorn = mkUniqSet $ map patchF $ uniqSetToList $ liveBorn live
, liveDieRead = mkUniqSet $ map patchF $ uniqSetToList $ liveDieRead live
, liveDieWrite = mkUniqSet $ map patchF $ uniqSetToList $ liveDieWrite live })
--------------------------------------------------------------------------------
-- | Convert a NatCmmDecl to a LiveCmmDecl, with empty liveness information
natCmmTopToLive
:: Instruction instr
=> NatCmmDecl statics instr
-> LiveCmmDecl statics instr
natCmmTopToLive (CmmData i d)
= CmmData i d
natCmmTopToLive (CmmProc info lbl (ListGraph []))
= CmmProc (LiveInfo info Nothing Nothing Map.empty) lbl []
natCmmTopToLive (CmmProc info lbl (ListGraph blocks@(first : _)))
= let first_id = blockId first
sccs = sccBlocks blocks
sccsLive = map (fmap (\(BasicBlock l instrs) ->
BasicBlock l (map (\i -> LiveInstr (Instr i) Nothing) instrs)))
$ sccs
in CmmProc (LiveInfo info (Just first_id) Nothing Map.empty) lbl sccsLive
sccBlocks
:: Instruction instr
=> [NatBasicBlock instr]
-> [SCC (NatBasicBlock instr)]
sccBlocks blocks = stronglyConnCompFromEdgedVertices graph
where
getOutEdges :: Instruction instr => [instr] -> [BlockId]
getOutEdges instrs = concat $ map jumpDestsOfInstr instrs
graph = [ (block, getUnique id, map getUnique (getOutEdges instrs))
| block@(BasicBlock id instrs) <- blocks ]
---------------------------------------------------------------------------------
-- Annotate code with register liveness information
--
regLiveness
:: (PlatformOutputable instr, Instruction instr)
=> Platform
-> LiveCmmDecl statics instr
-> UniqSM (LiveCmmDecl statics instr)
regLiveness _ (CmmData i d)
= returnUs $ CmmData i d
regLiveness _ (CmmProc info lbl [])
| LiveInfo static mFirst _ _ <- info
= returnUs $ CmmProc
(LiveInfo static mFirst (Just mapEmpty) Map.empty)
lbl []
regLiveness platform (CmmProc info lbl sccs)
| LiveInfo static mFirst _ liveSlotsOnEntry <- info
= let (ann_sccs, block_live) = computeLiveness platform sccs
in returnUs $ CmmProc (LiveInfo static mFirst (Just block_live) liveSlotsOnEntry)
lbl ann_sccs
-- -----------------------------------------------------------------------------
-- | Check ordering of Blocks
-- The computeLiveness function requires SCCs to be in reverse dependent order.
-- If they're not the liveness information will be wrong, and we'll get a bad allocation.
-- Better to check for this precondition explicitly or some other poor sucker will
-- waste a day staring at bad assembly code..
--
checkIsReverseDependent
:: Instruction instr
=> [SCC (LiveBasicBlock instr)] -- ^ SCCs of blocks that we're about to run the liveness determinator on.
-> Maybe BlockId -- ^ BlockIds that fail the test (if any)
checkIsReverseDependent sccs'
= go emptyUniqSet sccs'
where go _ []
= Nothing
go blocksSeen (AcyclicSCC block : sccs)
= let dests = slurpJumpDestsOfBlock block
blocksSeen' = unionUniqSets blocksSeen $ mkUniqSet [blockId block]
badDests = dests `minusUniqSet` blocksSeen'
in case uniqSetToList badDests of
[] -> go blocksSeen' sccs
bad : _ -> Just bad
go blocksSeen (CyclicSCC blocks : sccs)
= let dests = unionManyUniqSets $ map slurpJumpDestsOfBlock blocks
blocksSeen' = unionUniqSets blocksSeen $ mkUniqSet $ map blockId blocks
badDests = dests `minusUniqSet` blocksSeen'
in case uniqSetToList badDests of
[] -> go blocksSeen' sccs
bad : _ -> Just bad
slurpJumpDestsOfBlock (BasicBlock _ instrs)
= unionManyUniqSets
$ map (mkUniqSet . jumpDestsOfInstr)
[ i | LiveInstr i _ <- instrs]
-- | If we've compute liveness info for this code already we have to reverse
-- the SCCs in each top to get them back to the right order so we can do it again.
reverseBlocksInTops :: LiveCmmDecl statics instr -> LiveCmmDecl statics instr
reverseBlocksInTops top
= case top of
CmmData{} -> top
CmmProc info lbl sccs -> CmmProc info lbl (reverse sccs)
-- | Computing liveness
--
-- On entry, the SCCs must be in "reverse" order: later blocks may transfer
-- control to earlier ones only, else `panic`.
--
-- The SCCs returned are in the *opposite* order, which is exactly what we
-- want for the next pass.
--
computeLiveness
:: (PlatformOutputable instr, Instruction instr)
=> Platform
-> [SCC (LiveBasicBlock instr)]
-> ([SCC (LiveBasicBlock instr)], -- instructions annotated with list of registers
-- which are "dead after this instruction".
BlockMap RegSet) -- blocks annontated with set of live registers
-- on entry to the block.
computeLiveness platform sccs
= case checkIsReverseDependent sccs of
Nothing -> livenessSCCs emptyBlockMap [] sccs
Just bad -> pprPanic "RegAlloc.Liveness.computeLivenss"
(vcat [ text "SCCs aren't in reverse dependent order"
, text "bad blockId" <+> ppr bad
, pprPlatform platform sccs])
livenessSCCs
:: Instruction instr
=> BlockMap RegSet
-> [SCC (LiveBasicBlock instr)] -- accum
-> [SCC (LiveBasicBlock instr)]
-> ( [SCC (LiveBasicBlock instr)]
, BlockMap RegSet)
livenessSCCs blockmap done []
= (done, blockmap)
livenessSCCs blockmap done (AcyclicSCC block : sccs)
= let (blockmap', block') = livenessBlock blockmap block
in livenessSCCs blockmap' (AcyclicSCC block' : done) sccs
livenessSCCs blockmap done
(CyclicSCC blocks : sccs) =
livenessSCCs blockmap' (CyclicSCC blocks':done) sccs
where (blockmap', blocks')
= iterateUntilUnchanged linearLiveness equalBlockMaps
blockmap blocks
iterateUntilUnchanged
:: (a -> b -> (a,c)) -> (a -> a -> Bool)
-> a -> b
-> (a,c)
iterateUntilUnchanged f eq a b
= head $
concatMap tail $
groupBy (\(a1, _) (a2, _) -> eq a1 a2) $
iterate (\(a, _) -> f a b) $
(a, panic "RegLiveness.livenessSCCs")
linearLiveness
:: Instruction instr
=> BlockMap RegSet -> [LiveBasicBlock instr]
-> (BlockMap RegSet, [LiveBasicBlock instr])
linearLiveness = mapAccumL livenessBlock
-- probably the least efficient way to compare two
-- BlockMaps for equality.
equalBlockMaps a b
= a' == b'
where a' = map f $ mapToList a
b' = map f $ mapToList b
f (key,elt) = (key, uniqSetToList elt)
-- | Annotate a basic block with register liveness information.
--
livenessBlock
:: Instruction instr
=> BlockMap RegSet
-> LiveBasicBlock instr
-> (BlockMap RegSet, LiveBasicBlock instr)
livenessBlock blockmap (BasicBlock block_id instrs)
= let
(regsLiveOnEntry, instrs1)
= livenessBack emptyUniqSet blockmap [] (reverse instrs)
blockmap' = mapInsert block_id regsLiveOnEntry blockmap
instrs2 = livenessForward regsLiveOnEntry instrs1
output = BasicBlock block_id instrs2
in ( blockmap', output)
-- | Calculate liveness going forwards,
-- filling in when regs are born
livenessForward
:: Instruction instr
=> RegSet -- regs live on this instr
-> [LiveInstr instr] -> [LiveInstr instr]
livenessForward _ [] = []
livenessForward rsLiveEntry (li@(LiveInstr instr mLive) : lis)
| Nothing <- mLive
= li : livenessForward rsLiveEntry lis
| Just live <- mLive
, RU _ written <- regUsageOfInstr instr
= let
-- Regs that are written to but weren't live on entry to this instruction
-- are recorded as being born here.
rsBorn = mkUniqSet
$ filter (\r -> not $ elementOfUniqSet r rsLiveEntry) written
rsLiveNext = (rsLiveEntry `unionUniqSets` rsBorn)
`minusUniqSet` (liveDieRead live)
`minusUniqSet` (liveDieWrite live)
in LiveInstr instr (Just live { liveBorn = rsBorn })
: livenessForward rsLiveNext lis
livenessForward _ _ = panic "RegLiveness.livenessForward: no match"
-- | Calculate liveness going backwards,
-- filling in when regs die, and what regs are live across each instruction
livenessBack
:: Instruction instr
=> RegSet -- regs live on this instr
-> BlockMap RegSet -- regs live on entry to other BBs
-> [LiveInstr instr] -- instructions (accum)
-> [LiveInstr instr] -- instructions
-> (RegSet, [LiveInstr instr])
livenessBack liveregs _ done [] = (liveregs, done)
livenessBack liveregs blockmap acc (instr : instrs)
= let (liveregs', instr') = liveness1 liveregs blockmap instr
in livenessBack liveregs' blockmap (instr' : acc) instrs
-- don't bother tagging comments or deltas with liveness
liveness1
:: Instruction instr
=> RegSet
-> BlockMap RegSet
-> LiveInstr instr
-> (RegSet, LiveInstr instr)
liveness1 liveregs _ (LiveInstr instr _)
| isMetaInstr instr
= (liveregs, LiveInstr instr Nothing)
liveness1 liveregs blockmap (LiveInstr instr _)
| not_a_branch
= (liveregs1, LiveInstr instr
(Just $ Liveness
{ liveBorn = emptyUniqSet
, liveDieRead = mkUniqSet r_dying
, liveDieWrite = mkUniqSet w_dying }))
| otherwise
= (liveregs_br, LiveInstr instr
(Just $ Liveness
{ liveBorn = emptyUniqSet
, liveDieRead = mkUniqSet r_dying_br
, liveDieWrite = mkUniqSet w_dying }))
where
!(RU read written) = regUsageOfInstr instr
-- registers that were written here are dead going backwards.
-- registers that were read here are live going backwards.
liveregs1 = (liveregs `delListFromUniqSet` written)
`addListToUniqSet` read
-- registers that are not live beyond this point, are recorded
-- as dying here.
r_dying = [ reg | reg <- read, reg `notElem` written,
not (elementOfUniqSet reg liveregs) ]
w_dying = [ reg | reg <- written,
not (elementOfUniqSet reg liveregs) ]
-- union in the live regs from all the jump destinations of this
-- instruction.
targets = jumpDestsOfInstr instr -- where we go from here
not_a_branch = null targets
targetLiveRegs target
= case mapLookup target blockmap of
Just ra -> ra
Nothing -> emptyRegMap
live_from_branch = unionManyUniqSets (map targetLiveRegs targets)
liveregs_br = liveregs1 `unionUniqSets` live_from_branch
-- registers that are live only in the branch targets should
-- be listed as dying here.
live_branch_only = live_from_branch `minusUniqSet` liveregs
r_dying_br = uniqSetToList (mkUniqSet r_dying `unionUniqSets`
live_branch_only)
| mcmaniac/ghc | compiler/nativeGen/RegAlloc/Liveness.hs | Haskell | bsd-3-clause | 34,755 |
-- Copyright (c) 2016-present, Facebook, Inc.
-- All rights reserved.
--
-- This source code is licensed under the BSD-style license found in the
-- LICENSE file in the root directory of this source tree. An additional grant
-- of patent rights can be found in the PATENTS file in the same directory.
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Duration.NB.Corpus
( corpus
) where
import Prelude
import Data.String
import Duckling.Duration.Types
import Duckling.Lang
import Duckling.Resolve
import Duckling.Testing.Types
import Duckling.TimeGrain.Types (Grain(..))
corpus :: Corpus
corpus = (testContext {lang = NB}, allExamples)
allExamples :: [Example]
allExamples = concat
[ examples (DurationData 1 Second)
[ "1 sek"
, "en sek"
, "ett sekund"
, "e sekunder"
]
, examples (DurationData 30 Minute)
[ "tredve min"
, "30 minutt"
, "30 minutter"
, "1/2 time"
, "en halv time"
]
, examples (DurationData 2 Day)
[ "et par dager"
, "2 dag"
, "to dag"
]
]
| rfranek/duckling | Duckling/Duration/NB/Corpus.hs | Haskell | bsd-3-clause | 1,172 |
module System.IO.Streams.Serialize where
import Data.ByteString
import Data.Serialize
import System.IO.Streams as Streams
decodeFromStream :: Serialize a => InputStream ByteString -> IO (InputStream a)
decodeFromStream = Streams.map (fromEither . decode)
where
fromEither (Left s) = error s
fromEither (Right x) = x
encodeToStream :: Serialize a => InputStream a -> IO (InputStream ByteString)
encodeToStream = Streams.map encode
| WraithM/peertrader-backend | src/System/IO/Streams/Serialize.hs | Haskell | bsd-3-clause | 473 |
{-# LANGUAGE OverloadedStrings, DeriveDataTypeable, GeneralizedNewtypeDeriving #-}
{-# OPTIONS_HADDOCK not-home #-}
-- |Internal functions used to implement the functions exported by
-- "Test.WebDriver.Commands". These may be useful for implementing non-standard
-- webdriver commands.
module Test.WebDriver.Commands.Internal
(-- * Low-level webdriver functions
doCommand
-- ** Commands with :sessionId URL parameter
, doSessCommand, SessionId(..)
-- ** Commands with element :id URL parameters
, doElemCommand, Element(..)
-- ** Commands with :windowHandle URL parameters
, doWinCommand, WindowHandle(..), currentWindow
-- * Exceptions
, NoSessionId(..)
) where
import Test.WebDriver.Class
import Test.WebDriver.Session
import Test.WebDriver.Utils (urlEncode)
import Data.Aeson
import Data.Aeson.Types
import Data.Text (Text)
import qualified Data.Text as T
import Control.Exception.Lifted
import Data.Typeable
import Data.Default.Class
import Control.Applicative
import Prelude -- hides some "unused import" warnings
{- |An opaque identifier for a web page element. -}
newtype Element = Element Text
deriving (Eq, Ord, Show, Read)
instance FromJSON Element where
parseJSON (Object o) = Element <$> o .: "ELEMENT"
parseJSON v = typeMismatch "Element" v
instance ToJSON Element where
toJSON (Element e) = object ["ELEMENT" .= e]
{- |An opaque identifier for a browser window -}
newtype WindowHandle = WindowHandle Text
deriving (Eq, Ord, Show, Read,
FromJSON, ToJSON)
instance Default WindowHandle where
def = currentWindow
-- |A special 'WindowHandle' that always refers to the currently focused window.
-- This is also used by the 'Default' instance.
currentWindow :: WindowHandle
currentWindow = WindowHandle "current"
instance Exception NoSessionId
-- |A command requiring a session ID was attempted when no session ID was
-- available.
newtype NoSessionId = NoSessionId String
deriving (Eq, Show, Typeable)
-- |This a convenient wrapper around 'doCommand' that automatically prepends
-- the session URL parameter to the wire command URL. For example, passing
-- a URL of \"/refresh\" will expand to \"/session/:sessionId/refresh\", where
-- :sessionId is a URL parameter as described in
-- <https://github.com/SeleniumHQ/selenium/wiki/JsonWireProtocol>
doSessCommand :: (WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand method path args = do
WDSession { wdSessId = mSessId } <- getSession
case mSessId of
Nothing -> throwIO . NoSessionId $ msg
where
msg = "doSessCommand: No session ID found for relative URL "
++ show path
Just (SessionId sId) -> doCommand method
(T.concat ["/session/", urlEncode sId, path]) args
-- |A wrapper around 'doSessCommand' to create element URLs.
-- For example, passing a URL of "/active" will expand to
-- \"/session/:sessionId/element/:id/active\", where :sessionId and :id are URL
-- parameters as described in the wire protocol.
doElemCommand :: (WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Element -> Text -> a -> wd b
doElemCommand m (Element e) path a =
doSessCommand m (T.concat ["/element/", urlEncode e, path]) a
-- |A wrapper around 'doSessCommand' to create window handle URLS.
-- For example, passing a URL of \"/size\" will expand to
-- \"/session/:sessionId/window/:windowHandle/\", where :sessionId and
-- :windowHandle are URL parameters as described in the wire protocol
doWinCommand :: (WebDriver wd, ToJSON a, FromJSON b) =>
Method -> WindowHandle -> Text -> a -> wd b
doWinCommand m (WindowHandle w) path a =
doSessCommand m (T.concat ["/window/", urlEncode w, path]) a
| zerobuzz/hs-webdriver | src/Test/WebDriver/Commands/Internal.hs | Haskell | bsd-3-clause | 3,893 |
import Control.Monad (void)
import qualified Graphics.UI.Threepenny as UI
import Graphics.UI.Threepenny.Core
{-----------------------------------------------------------------------------
Enabled
------------------------------------------------------------------------------}
main :: IO ()
main = startGUI defaultConfig setup
setup :: Window -> UI ()
setup w = void $ do
return w # set title "Input Elements"
button1 <- UI.button # set text "Me"
button2 <- UI.button # set text "You"
on UI.click button1 $ const $ do
element button1 # set UI.enabled False
element button2 # set UI.enabled True
on UI.click button2 $ const $ do
element button2 # set UI.enabled False
element button1 # set UI.enabled True
checkbox1 <- UI.input # set UI.type_ "checkbox"
status <- UI.span
on UI.click checkbox1 $ const $ do
b <- get UI.checked checkbox1
element status # set text ("checked:" ++ show b)
getBody w #+ [grid
[[string "enabled", element button1, element button2]
,[string "checked", element checkbox1, element status]
]]
| yuvallanger/threepenny-gui | samples/InputElements.hs | Haskell | bsd-3-clause | 1,143 |
{-# LANGUAGE CPP #-}
{-# LANGUAGE TupleSections #-}
module Eta.DeSugar.DsUsage (
-- * Dependency/fingerprinting code (used by MkIface)
mkUsageInfo, mkUsedNames, mkDependencies
) where
#include "HsVersions.h"
import Eta.Main.DynFlags
import Eta.Main.HscTypes
import Eta.TypeCheck.TcRnTypes
import Eta.BasicTypes.Name
import Eta.BasicTypes.NameSet
import Eta.BasicTypes.Module
import Eta.Utils.Outputable
import Eta.Utils.Util
import Eta.Utils.UniqSet
import Eta.Utils.UniqFM
import Eta.Utils.Fingerprint
import Eta.Utils.Maybes
import Data.List
import Data.IORef
import Data.Map (Map)
import qualified Data.Map as Map
import qualified Data.Set as Set
{- Note [Module self-dependency]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
RnNames.calculateAvails asserts the invariant that a module must not occur in
its own dep_orphs or dep_finsts. However, if we aren't careful this can occur
in the presence of hs-boot files: Consider that we have two modules, A and B,
both with hs-boot files,
A.hs contains a SOURCE import of B B.hs-boot contains a SOURCE import of A
A.hs-boot declares an orphan instance A.hs defines the orphan instance
In this case, B's dep_orphs will contain A due to its SOURCE import of A.
Consequently, A will contain itself in its imp_orphs due to its import of B.
This fact would end up being recorded in A's interface file. This would then
break the invariant asserted by calculateAvails that a module does not itself in
its dep_orphs. This was the cause of Trac #14128.
-}
-- | Extract information from the rename and typecheck phases to produce
-- a dependencies information for the module being compiled.
--
-- The first argument is additional dependencies from plugins
mkDependencies :: InstalledUnitId -> [Module] -> TcGblEnv -> IO Dependencies
mkDependencies iuid pluginModules
(TcGblEnv{ tcg_mod = mod,
tcg_imports = imports,
tcg_th_used = th_var
})
= do
-- Template Haskell used?
let (mns, ms) = unzip [ (moduleName mn, mn) | mn <- pluginModules ]
plugin_dep_mods = map (,False) mns
plugin_dep_pkgs = filter (/= iuid) (map (toInstalledUnitId . moduleUnitId) ms)
th_used <- readIORef th_var
let dep_mods = modDepsElts (delFromUFM (imp_dep_mods imports)
(moduleName mod))
++ plugin_dep_mods
-- M.hi-boot can be in the imp_dep_mods, but we must remove
-- it before recording the modules on which this one depends!
-- (We want to retain M.hi-boot in imp_dep_mods so that
-- loadHiBootInterface can see if M's direct imports depend
-- on M.hi-boot, and hence that we should do the hi-boot consistency
-- check.)
dep_orphs = filter (/= mod) (imp_orphs imports)
-- We must also remove self-references from imp_orphs. See
-- Note [Module self-dependency]
raw_pkgs = foldr Set.insert (imp_dep_pkgs imports) plugin_dep_pkgs
pkgs | th_used = Set.insert (toInstalledUnitId thUnitId) raw_pkgs
| otherwise = raw_pkgs
-- Set the packages required to be Safe according to Safe Haskell.
-- See Note [RnNames . Tracking Trust Transitively]
sorted_pkgs = sort (Set.toList pkgs)
trust_pkgs = imp_trust_pkgs imports
dep_pkgs' = map (\x -> (x, x `Set.member` trust_pkgs)) sorted_pkgs
return Deps { dep_mods = dep_mods,
dep_pkgs = dep_pkgs',
dep_orphs = dep_orphs,
dep_finsts = sortBy stableModuleCmp (imp_finsts imports) }
-- sort to get into canonical order
-- NB. remember to use lexicographic ordering
mkUsedNames :: TcGblEnv -> NameSet
mkUsedNames TcGblEnv{ tcg_dus = dus } = allUses dus
mkUsageInfo :: HscEnv -> Module -> ImportedMods
-> NameSet -> [FilePath] -> [(Module, Fingerprint)]
-> IO [Usage]
mkUsageInfo hsc_env this_mod dir_imp_mods used_names dependent_files merged
= do
eps <- hscEPS hsc_env
hashes <- mapM getFileHash dependent_files
let mod_usages = mk_mod_usage_info (eps_PIT eps) hsc_env this_mod
dir_imp_mods used_names
usages = mod_usages ++ [ UsageFile { usg_file_path = f
, usg_file_hash = hash }
| (f, hash) <- zip dependent_files hashes ]
++ [ UsageMergedRequirement
{ usg_mod = mod,
usg_mod_hash = hash
}
| (mod, hash) <- merged ]
usages `seqList` return usages
-- seq the list of Usages returned: occasionally these
-- don't get evaluated for a while and we can end up hanging on to
-- the entire collection of Ifaces.
mk_mod_usage_info :: PackageIfaceTable
-> HscEnv
-> Module
-> ImportedMods
-> NameSet
-> [Usage]
mk_mod_usage_info pit hsc_env this_mod direct_imports used_names
= mapMaybe mkUsage usage_mods
where
hpt = hsc_HPT hsc_env
dflags = hsc_dflags hsc_env
this_pkg = thisPackage dflags
used_mods = moduleEnvKeys ent_map
dir_imp_mods = moduleEnvKeys direct_imports
all_mods = used_mods ++ filter (`notElem` used_mods) dir_imp_mods
usage_mods = sortBy stableModuleCmp all_mods
-- canonical order is imported, to avoid interface-file
-- wobblage.
-- ent_map groups together all the things imported and used
-- from a particular module
ent_map :: ModuleEnv [OccName]
ent_map = nonDetFoldUniqSet add_mv emptyModuleEnv used_names
-- nonDetFoldUFM is OK here. If you follow the logic, we sort by OccName
-- in ent_hashs
where
add_mv name mv_map
| isWiredInName name = mv_map -- ignore wired-in names
| otherwise
= case nameModule_maybe name of
Nothing -> ASSERT2( isSystemName name, ppr name ) mv_map
-- See Note [Internal used_names]
Just mod ->
-- See Note [Identity versus semantic module]
let mod' = if isHoleModule mod
then mkModule this_pkg (moduleName mod)
else mod
-- This lambda function is really just a
-- specialised (++); originally came about to
-- avoid quadratic behaviour (trac #2680)
in extendModuleEnvWith (\_ xs -> occ:xs) mv_map mod' [occ]
where occ = nameOccName name
-- We want to create a Usage for a home module if
-- a) we used something from it; has something in used_names
-- b) we imported it, even if we used nothing from it
-- (need to recompile if its export list changes: export_fprint)
mkUsage :: Module -> Maybe Usage
mkUsage mod
| isNothing maybe_iface -- We can't depend on it if we didn't
-- load its interface.
|| mod == this_mod -- We don't care about usages of
-- things in *this* module
= Nothing
| moduleUnitId mod /= this_pkg
= Just UsagePackageModule{ usg_mod = mod,
usg_mod_hash = mod_hash,
usg_safe = imp_safe }
-- for package modules, we record the module hash only
| (null used_occs
&& isNothing export_hash
&& not is_direct_import
&& not finsts_mod)
= Nothing -- Record no usage info
-- for directly-imported modules, we always want to record a usage
-- on the orphan hash. This is what triggers a recompilation if
-- an orphan is added or removed somewhere below us in the future.
| otherwise
= Just UsageHomeModule {
usg_mod_name = moduleName mod,
usg_mod_hash = mod_hash,
usg_exports = export_hash,
usg_entities = Map.toList ent_hashs,
usg_safe = imp_safe }
where
maybe_iface = lookupIfaceByModule dflags hpt pit mod
-- In one-shot mode, the interfaces for home-package
-- modules accumulate in the PIT not HPT. Sigh.
Just iface = maybe_iface
finsts_mod = mi_finsts iface
hash_env = mi_hash_fn iface
mod_hash = mi_mod_hash iface
export_hash | depend_on_exports = Just (mi_exp_hash iface)
| otherwise = Nothing
by_is_safe (ImportedByUser imv) = imv_is_safe imv
by_is_safe _ = False
(is_direct_import, imp_safe)
= case lookupModuleEnv direct_imports mod of
-- ezyang: I'm not sure if any is the correct
-- metric here. If safety was guaranteed to be uniform
-- across all imports, why did the old code only look
-- at the first import?
Just bys -> (True, any by_is_safe bys)
Nothing -> (False, safeImplicitImpsReq dflags)
-- Nothing case is for references to entities which were
-- not directly imported (NB: the "implicit" Prelude import
-- counts as directly imported! An entity is not directly
-- imported if, e.g., we got a reference to it from a
-- reexport of another module.)
used_occs = lookupModuleEnv ent_map mod `orElse` []
-- Making a Map here ensures that (a) we remove duplicates
-- when we have usages on several subordinates of a single parent,
-- and (b) that the usages emerge in a canonical order, which
-- is why we use Map rather than OccEnv: Map works
-- using Ord on the OccNames, which is a lexicographic ordering.
ent_hashs :: Map OccName Fingerprint
ent_hashs = Map.fromList (map lookup_occ used_occs)
lookup_occ occ =
case hash_env occ of
Nothing -> pprPanic "mkUsage" (ppr mod <+> ppr occ <+> ppr used_names)
Just r -> r
depend_on_exports = is_direct_import
{- True
Even if we used 'import M ()', we have to register a
usage on the export list because we are sensitive to
changes in orphan instances/rules.
False
In GHC 6.8.x we always returned true, and in
fact it recorded a dependency on *all* the
modules underneath in the dependency tree. This
happens to make orphans work right, but is too
expensive: it'll read too many interface files.
The 'isNothing maybe_iface' check above saved us
from generating many of these usages (at least in
one-shot mode), but that's even more bogus!
-}
| rahulmutt/ghcvm | compiler/Eta/DeSugar/DsUsage.hs | Haskell | bsd-3-clause | 11,256 |
{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, DeriveFunctor,
DeriveDataTypeable, PatternGuards #-}
{-# OPTIONS_GHC -fwarn-incomplete-patterns #-}
{-| TT is the core language of Idris. The language has:
* Full dependent types
* A hierarchy of universes, with cumulativity: Type : Type1, Type1 : Type2, ...
* Pattern matching letrec binding
* (primitive types defined externally)
Some technical stuff:
* Typechecker is kept as simple as possible - no unification, just a checker for incomplete terms.
* We have a simple collection of tactics which we use to elaborate source
programs with implicit syntax into fully explicit terms.
-}
module Idris.Core.TT(AppStatus(..), ArithTy(..), Binder(..), Const(..), Ctxt(..),
ConstraintFC(..), DataOpt(..), DataOpts(..), Datatype(..),
Env(..), EnvTT(..), Err(..), Err'(..), ErrorReportPart(..),
FC(..), FC'(..), ImplicitInfo(..), IntTy(..), Name(..),
NameOutput(..), NameType(..), NativeTy(..), OutputAnnotation(..),
Provenance(..), Raw(..), SpecialName(..), TC(..), Term(..),
TermSize(..), TextFormatting(..), TT(..),Type(..), TypeInfo(..),
UConstraint(..), UCs(..), UExp(..), Universe(..),
addAlist, addBinder, addDef, allTTNames, arity, bindAll,
bindingOf, bindTyArgs, constDocs, constIsType, deleteDefExact,
discard, emptyContext, emptyFC, explicitNames, fc_end, fc_fname,
fc_start, fcIn, fileFC, finalise, fmapMB, forget, forgetEnv,
freeNames, getArgTys, getRetTy, implicitable, instantiate,
intTyName, isInjective, isTypeConst, liftPats, lookupCtxt,
lookupCtxtExact, lookupCtxtName, mapCtxt, mkApp, nativeTyWidth,
nextName, noOccurrence, nsroot, occurrences, orderPats,
pEraseType, pmap, pprintRaw, pprintTT, prettyEnv, psubst, pToV,
pToVs, pureTerm, raw_apply, raw_unapply, refsIn, safeForget,
safeForgetEnv, showCG, showEnv, showEnvDbg, showSep,
sInstanceN, sMN, sNS, spanFC, str, subst, substNames, substTerm,
substV, sUN, tcname, termSmallerThan, tfail, thead, tnull,
toAlist, traceWhen, txt, unApply, uniqueBinders, uniqueName,
uniqueNameFrom, uniqueNameSet, unList, updateDef, vToP, weakenTm) where
-- Work around AMP without CPP
import Prelude (Eq(..), Show(..), Ord(..), Functor(..), Monad(..), String, Int,
Integer, Ordering(..), Maybe(..), Num(..), Bool(..), Enum(..),
Read(..), FilePath, Double, (&&), (||), ($), (.), div, error, fst,
snd, not, mod, read, otherwise)
import Control.Applicative (Applicative (..), Alternative)
import qualified Control.Applicative as A (Alternative (..))
import Control.Monad.State.Strict
import Control.Monad.Trans.Except (Except (..))
import Debug.Trace
import qualified Data.Map.Strict as Map
import Data.Char
import Data.Data (Data)
import Numeric (showIntAtBase)
import qualified Data.Text as T
import Data.List hiding (group, insert)
import Data.Set(Set, member, fromList, insert)
import Data.Maybe (listToMaybe)
import Data.Foldable (Foldable)
import Data.Traversable (Traversable)
import Data.Typeable (Typeable)
import Data.Vector.Unboxed (Vector)
import qualified Data.Vector.Unboxed as V
import qualified Data.Binary as B
import Data.Binary hiding (get, put)
import Foreign.Storable (sizeOf)
import Util.Pretty hiding (Str)
data Option = TTypeInTType
| CheckConv
deriving Eq
-- | Source location. These are typically produced by the parser 'Idris.Parser.getFC'
data FC = FC { _fc_fname :: String, -- ^ Filename
_fc_start :: (Int, Int), -- ^ Line and column numbers for the start of the location span
_fc_end :: (Int, Int) -- ^ Line and column numbers for the end of the location span
}
| NoFC -- ^ Locations for machine-generated terms
| FileFC { _fc_fname :: String } -- ^ Locations with file only
deriving (Data, Typeable, Ord)
-- TODO: find uses and destroy them, doing this case analysis at call sites
-- | Give a notion of filename associated with an FC
fc_fname :: FC -> String
fc_fname (FC f _ _) = f
fc_fname NoFC = "(no file)"
fc_fname (FileFC f) = f
-- TODO: find uses and destroy them, doing this case analysis at call sites
-- | Give a notion of start location associated with an FC
fc_start :: FC -> (Int, Int)
fc_start (FC _ start _) = start
fc_start NoFC = (0, 0)
fc_start (FileFC f) = (0, 0)
-- TODO: find uses and destroy them, doing this case analysis at call sites
-- | Give a notion of end location associated with an FC
fc_end :: FC -> (Int, Int)
fc_end (FC _ _ end) = end
fc_end NoFC = (0, 0)
fc_end (FileFC f) = (0, 0)
-- | Get the largest span containing the two FCs
spanFC :: FC -> FC -> FC
spanFC (FC f start end) (FC f' start' end')
| f == f' = FC f (minLocation start start') (maxLocation end end')
| otherwise = NoFC
where minLocation (l, c) (l', c') =
case compare l l' of
LT -> (l, c)
EQ -> (l, min c c')
GT -> (l', c')
maxLocation (l, c) (l', c') =
case compare l l' of
LT -> (l', c')
EQ -> (l, max c c')
GT -> (l, c)
spanFC fc@(FC f _ _) (FileFC f') | f == f' = fc
| otherwise = NoFC
spanFC (FileFC f') fc@(FC f _ _) | f == f' = fc
| otherwise = NoFC
spanFC (FileFC f) (FileFC f') | f == f' = FileFC f
| otherwise = NoFC
spanFC NoFC fc = fc
spanFC fc NoFC = fc
-- | Determine whether the first argument is completely contained in the second
fcIn :: FC -> FC -> Bool
fcIn NoFC _ = False
fcIn (FileFC _) _ = False
fcIn (FC {}) NoFC = False
fcIn (FC {}) (FileFC _) = False
fcIn (FC fn1 (sl1, sc1) (el1, ec1)) (FC fn2 (sl2, sc2) (el2, ec2)) =
fn1 == fn2 &&
(sl1 == sl2 && sc1 > sc2 || sl1 > sl2) &&
(el1 == el2 && ec1 < ec2 || el1 < el2)
-- | Ignore source location equality (so deriving classes do not compare FCs)
instance Eq FC where
_ == _ = True
-- | FC with equality
newtype FC' = FC' { unwrapFC :: FC }
instance Eq FC' where
FC' fc == FC' fc' = fcEq fc fc'
where fcEq (FC n s e) (FC n' s' e') = n == n' && s == s' && e == e'
fcEq NoFC NoFC = True
fcEq (FileFC f) (FileFC f') = f == f'
fcEq _ _ = False
-- | Empty source location
emptyFC :: FC
emptyFC = NoFC
-- | Source location with file only
fileFC :: String -> FC
fileFC s = FileFC s
{-!
deriving instance Binary FC
deriving instance NFData FC
!-}
instance Sized FC where
size (FC f s e) = 4 + length f
size NoFC = 1
size (FileFC f) = length f
instance Show FC where
show (FC f s e) = f ++ ":" ++ showLC s e
where showLC (sl, sc) (el, ec) | sl == el && sc == ec = show sl ++ ":" ++ show sc
| sl == el = show sl ++ ":" ++ show sc ++ "-" ++ show ec
| otherwise = show sl ++ ":" ++ show sc ++ "-" ++ show el ++ ":" ++ show ec
show NoFC = "No location"
show (FileFC f) = f
-- | Output annotation for pretty-printed name - decides colour
data NameOutput = TypeOutput | FunOutput | DataOutput | MetavarOutput | PostulateOutput deriving (Show, Eq)
-- | Text formatting output
data TextFormatting = BoldText | ItalicText | UnderlineText deriving (Show, Eq)
-- | Output annotations for pretty-printing
data OutputAnnotation = AnnName Name (Maybe NameOutput) (Maybe String) (Maybe String)
-- ^^ The name, classification, docs overview, and pretty-printed type
| AnnBoundName Name Bool
-- ^^ The name and whether it is implicit
| AnnConst Const
| AnnData String String -- ^ type, doc overview
| AnnType String String -- ^ name, doc overview
| AnnKeyword
| AnnFC FC
| AnnTextFmt TextFormatting
| AnnLink String -- ^ A link to this URL
| AnnTerm [(Name, Bool)] (TT Name) -- ^ pprint bound vars, original term
| AnnSearchResult Ordering -- ^ more general, isomorphic, or more specific
| AnnErr Err
| AnnNamespace [T.Text] (Maybe FilePath)
-- ^ A namespace (e.g. on an import line or in
-- a namespace declaration). Stored starting
-- at the root, with the hierarchy fully
-- resolved. If a file path is present, then
-- the namespace represents a module imported
-- from that file.
| AnnQuasiquote
| AnnAntiquote
deriving (Show, Eq)
-- | Used for error reflection
data ErrorReportPart = TextPart String
| NamePart Name
| TermPart Term
| RawPart Raw
| SubReport [ErrorReportPart]
deriving (Show, Eq, Data, Typeable)
data Provenance = ExpectedType
| TooManyArgs Term
| InferredVal
| GivenVal
| SourceTerm Term
deriving (Show, Eq, Data, Typeable)
{-!
deriving instance NFData Err
deriving instance Binary Err
!-}
-- NB: Please remember to keep Err synchronised with
-- Language.Reflection.Errors.Err in the stdlib!
-- | Idris errors. Used as exceptions in the compiler, but reported to users
-- if they reach the top level.
data Err' t
= Msg String
| InternalMsg String
| CantUnify Bool (t, Maybe Provenance) -- Expected type, provenance
(t, Maybe Provenance) -- Actual type, provenance
(Err' t) [(Name, t)] Int
-- Int is 'score' - how much we did unify
-- Bool indicates recoverability, True indicates more info may make
-- unification succeed
| InfiniteUnify Name t [(Name, t)]
| CantConvert t t [(Name, t)]
| CantSolveGoal t [(Name, t)]
| UnifyScope Name Name t [(Name, t)]
| CantInferType String
| NonFunctionType t t
| NotEquality t t
| TooManyArguments Name
| CantIntroduce t
| NoSuchVariable Name
| WithFnType t
| NoTypeDecl Name
| NotInjective t t t
| CantResolve Bool -- True if postponed, False if fatal
t
| InvalidTCArg Name t
| CantResolveAlts [Name]
| NoValidAlts [Name]
| IncompleteTerm t
| NoEliminator String t
| UniverseError FC UExp (Int, Int) (Int, Int) [ConstraintFC]
-- ^ Location, bad universe, old domain, new domain, suspects
| UniqueError Universe Name
| UniqueKindError Universe Name
| ProgramLineComment
| Inaccessible Name
| UnknownImplicit Name Name
| CantMatch t
| NonCollapsiblePostulate Name
| AlreadyDefined Name
| ProofSearchFail (Err' t)
| NoRewriting t
| At FC (Err' t)
| Elaborating String Name (Err' t)
| ElaboratingArg Name Name [(Name, Name)] (Err' t)
| ProviderError String
| LoadingFailed String (Err' t)
| ReflectionError [[ErrorReportPart]] (Err' t)
| ReflectionFailed String (Err' t)
| ElabScriptDebug [ErrorReportPart] t [(Name, t, [(Name, Binder t)])]
-- ^ User-specified message, proof term, goals with context (first goal is focused)
| ElabScriptStuck t
deriving (Eq, Functor, Data, Typeable)
type Err = Err' Term
data TC a = OK !a
| Error Err
deriving (Eq, Functor)
bindTC :: TC a -> (a -> TC b) -> TC b
bindTC x k = case x of
OK v -> k v
Error e -> Error e
{-# INLINE bindTC #-}
instance Monad TC where
return x = OK x
x >>= k = bindTC x k
fail e = Error (InternalMsg e)
instance MonadPlus TC where
mzero = fail "Unknown error"
(OK x) `mplus` _ = OK x
_ `mplus` (OK y) = OK y
err `mplus` _ = err
instance Applicative TC where
pure = return
(<*>) = ap
instance Alternative TC where
empty = mzero
(<|>) = mplus
{-!
deriving instance NFData Err
!-}
instance Sized ErrorReportPart where
size (TextPart msg) = 1 + length msg
size (TermPart t) = 1 + size t
size (RawPart r) = 1 + size r
size (NamePart n) = 1 + size n
size (SubReport rs) = 1 + size rs
instance Sized Err where
size (Msg msg) = length msg
size (InternalMsg msg) = length msg
size (CantUnify _ left right err _ score) = size (fst left) + size (fst right) + size err
size (InfiniteUnify _ right _) = size right
size (CantConvert left right _) = size left + size right
size (UnifyScope _ _ right _) = size right
size (NoSuchVariable name) = size name
size (NoTypeDecl name) = size name
size (NotInjective l c r) = size l + size c + size r
size (CantResolve _ trm) = size trm
size (NoRewriting trm) = size trm
size (CantResolveAlts _) = 1
size (IncompleteTerm trm) = size trm
size ProgramLineComment = 1
size (At fc err) = size fc + size err
size (Elaborating _ n err) = size err
size (ElaboratingArg _ _ _ err) = size err
size (ProviderError msg) = length msg
size (LoadingFailed fn e) = 1 + length fn + size e
size _ = 1
instance Show Err where
show (Msg s) = s
show (InternalMsg s) = "Internal error: " ++ show s
show (CantUnify rcv l r e sc i) = "CantUnify " ++ show rcv ++ " " ++
show l ++ " " ++ show r ++ " " ++
show e ++ " in " ++ show sc ++ " " ++ show i
show (CantSolveGoal g _) = "CantSolve " ++ show g
show (Inaccessible n) = show n ++ " is not an accessible pattern variable"
show (UnknownImplicit n f) = show n ++ " is not an implicit argument of " ++ show f
show (ProviderError msg) = "Type provider error: " ++ msg
show (LoadingFailed fn e) = "Loading " ++ fn ++ " failed: (TT) " ++ show e
show ProgramLineComment = "Program line next to comment"
show (At f e) = show f ++ ":" ++ show e
show (ElaboratingArg f x prev e) = "Elaborating " ++ show f ++ " arg " ++
show x ++ ": " ++ show e
show (Elaborating what n e) = "Elaborating " ++ what ++ show n ++ ":" ++ show e
show (ProofSearchFail e) = "Proof search fail: " ++ show e
show _ = "Error"
instance Pretty Err OutputAnnotation where
pretty (Msg m) = text m
pretty (CantUnify _ (l, _) (r, _) e _ i) =
text "Cannot unify" <+> colon <+> pretty l <+> text "and" <+> pretty r <+>
nest nestingSize (text "where" <+> pretty e <+> text "with" <+> (text . show $ i))
pretty (ProviderError msg) = text msg
pretty err@(LoadingFailed _ _) = text (show err)
pretty _ = text "Error"
instance (Pretty a OutputAnnotation) => Pretty (TC a) OutputAnnotation where
pretty (OK ok) = pretty ok
pretty (Error err) =
text "Error" <+> colon <+> pretty err
instance Show a => Show (TC a) where
show (OK x) = show x
show (Error str) = "Error: " ++ show str
tfail :: Err -> TC a
tfail e = Error e
failMsg :: String -> TC a
failMsg str = Error (Msg str)
trun :: FC -> TC a -> TC a
trun fc (OK a) = OK a
trun fc (Error e) = Error (At fc e)
discard :: Monad m => m a -> m ()
discard f = f >> return ()
showSep :: String -> [String] -> String
showSep sep [] = ""
showSep sep [x] = x
showSep sep (x:xs) = x ++ sep ++ showSep sep xs
pmap f (x, y) = (f x, f y)
traceWhen True msg a = trace msg a
traceWhen False _ a = a
-- RAW TERMS ----------------------------------------------------------------
-- | Names are hierarchies of strings, describing scope (so no danger of
-- duplicate names, but need to be careful on lookup).
data Name = UN T.Text -- ^ User-provided name
| NS Name [T.Text] -- ^ Root, namespaces
| MN Int T.Text -- ^ Machine chosen names
| NErased -- ^ Name of something which is never used in scope
| SN SpecialName -- ^ Decorated function names
| SymRef Int -- ^ Reference to IBC file symbol table (used during serialisation)
deriving (Eq, Ord, Data, Typeable)
txt :: String -> T.Text
txt = T.pack
str :: T.Text -> String
str = T.unpack
tnull :: T.Text -> Bool
tnull = T.null
thead :: T.Text -> Char
thead = T.head
-- Smart constructors for names, using old String style
sUN :: String -> Name
sUN s = UN (txt s)
sNS :: Name -> [String] -> Name
sNS n ss = NS n (map txt ss)
sMN :: Int -> String -> Name
sMN i s = MN i (txt s)
{-!
deriving instance Binary Name
deriving instance NFData Name
!-}
data SpecialName = WhereN Int Name Name
| WithN Int Name
| InstanceN Name [T.Text]
| ParentN Name T.Text
| MethodN Name
| CaseN Name
| ElimN Name
| InstanceCtorN Name
| MetaN Name Name
deriving (Eq, Ord, Data, Typeable)
{-!
deriving instance Binary SpecialName
deriving instance NFData SpecialName
!-}
sInstanceN :: Name -> [String] -> SpecialName
sInstanceN n ss = InstanceN n (map T.pack ss)
sParentN :: Name -> String -> SpecialName
sParentN n s = ParentN n (T.pack s)
instance Sized Name where
size (UN n) = 1
size (NS n els) = 1 + length els
size (MN i n) = 1
size _ = 1
instance Pretty Name OutputAnnotation where
pretty n@(UN n') = annotate (AnnName n Nothing Nothing Nothing) $ text (T.unpack n')
pretty n@(NS un s) = annotate (AnnName n Nothing Nothing Nothing) . noAnnotate $ pretty un
pretty n@(MN i s) = annotate (AnnName n Nothing Nothing Nothing) $
lbrace <+> text (T.unpack s) <+> (text . show $ i) <+> rbrace
pretty n@(SN s) = annotate (AnnName n Nothing Nothing Nothing) $ text (show s)
pretty n@(SymRef i) = annotate (AnnName n Nothing Nothing Nothing) $
text $ "##symbol" ++ show i ++ "##"
pretty NErased = annotate (AnnName NErased Nothing Nothing Nothing) $ text "_"
instance Pretty [Name] OutputAnnotation where
pretty = encloseSep empty empty comma . map pretty
instance Show Name where
show (UN n) = str n
show (NS n s) = showSep "." (map T.unpack (reverse s)) ++ "." ++ show n
show (MN _ u) | u == txt "underscore" = "_"
show (MN i s) = "{" ++ str s ++ show i ++ "}"
show (SN s) = show s
show (SymRef i) = "##symbol" ++ show i ++ "##"
show NErased = "_"
instance Show SpecialName where
show (WhereN i p c) = show p ++ ", " ++ show c
show (WithN i n) = "with block in " ++ show n
show (InstanceN cl inst) = showSep ", " (map T.unpack inst) ++ " instance of " ++ show cl
show (MethodN m) = "method " ++ show m
show (ParentN p c) = show p ++ "#" ++ T.unpack c
show (CaseN n) = "case block in " ++ show n
show (ElimN n) = "<<" ++ show n ++ " eliminator>>"
show (InstanceCtorN n) = "constructor of " ++ show n
show (MetaN parent meta) = "<<" ++ show parent ++ " " ++ show meta ++ ">>"
-- Show a name in a way decorated for code generation, not human reading
showCG :: Name -> String
showCG (UN n) = T.unpack n
showCG (NS n s) = showSep "." (map T.unpack (reverse s)) ++ "." ++ showCG n
showCG (MN _ u) | u == txt "underscore" = "_"
showCG (MN i s) = "{" ++ T.unpack s ++ show i ++ "}"
showCG (SN s) = showCG' s
where showCG' (WhereN i p c) = showCG p ++ ":" ++ showCG c ++ ":" ++ show i
showCG' (WithN i n) = "_" ++ showCG n ++ "_with_" ++ show i
showCG' (InstanceN cl inst) = '@':showCG cl ++ '$':showSep ":" (map T.unpack inst)
showCG' (MethodN m) = '!':showCG m
showCG' (ParentN p c) = showCG p ++ "#" ++ show c
showCG' (CaseN c) = showCG c ++ "_case"
showCG' (ElimN sn) = showCG sn ++ "_elim"
showCG' (InstanceCtorN n) = showCG n ++ "_ictor"
showCG' (MetaN parent meta) = showCG parent ++ "_meta_" ++ showCG meta
showCG (SymRef i) = error "can't do codegen for a symbol reference"
showCG NErased = "_"
-- |Contexts allow us to map names to things. A root name maps to a collection
-- of things in different namespaces with that name.
type Ctxt a = Map.Map Name (Map.Map Name a)
emptyContext = Map.empty
mapCtxt :: (a -> b) -> Ctxt a -> Ctxt b
mapCtxt = fmap . fmap
-- |Return True if the argument 'Name' should be interpreted as the name of a
-- typeclass.
tcname (UN xs) | T.null xs = False
| otherwise = T.head xs == '@'
tcname (NS n _) = tcname n
tcname (SN (InstanceN _ _)) = True
tcname (SN (MethodN _)) = True
tcname (SN (ParentN _ _)) = True
tcname _ = False
implicitable (NS n _) = implicitable n
implicitable (UN xs) | T.null xs = False
| otherwise = isLower (T.head xs) || T.head xs == '_'
implicitable (MN _ x) = not (tnull x) && thead x /= '_'
implicitable _ = False
nsroot (NS n _) = n
nsroot n = n
-- this will overwrite already existing definitions
addDef :: Name -> a -> Ctxt a -> Ctxt a
addDef n v ctxt = case Map.lookup (nsroot n) ctxt of
Nothing -> Map.insert (nsroot n)
(Map.insert n v Map.empty) ctxt
Just xs -> Map.insert (nsroot n)
(Map.insert n v xs) ctxt
{-| Look up a name in the context, given an optional namespace.
The name (n) may itself have a (partial) namespace given.
Rules for resolution:
- if an explicit namespace is given, return the names which match it. If none
match, return all names.
- if the name has has explicit namespace given, return the names which match it
and ignore the given namespace.
- otherwise, return all names.
-}
lookupCtxtName :: Name -> Ctxt a -> [(Name, a)]
lookupCtxtName n ctxt = case Map.lookup (nsroot n) ctxt of
Just xs -> filterNS (Map.toList xs)
Nothing -> []
where
filterNS [] = []
filterNS ((found, v) : xs)
| nsmatch n found = (found, v) : filterNS xs
| otherwise = filterNS xs
nsmatch (NS n ns) (NS p ps) = ns `isPrefixOf` ps
nsmatch (NS _ _) _ = False
nsmatch looking found = True
lookupCtxt :: Name -> Ctxt a -> [a]
lookupCtxt n ctxt = map snd (lookupCtxtName n ctxt)
lookupCtxtExact :: Name -> Ctxt a -> Maybe a
lookupCtxtExact n ctxt = listToMaybe [ v | (nm, v) <- lookupCtxtName n ctxt, nm == n]
deleteDefExact :: Name -> Ctxt a -> Ctxt a
deleteDefExact n = Map.adjust (Map.delete n) (nsroot n)
updateDef :: Name -> (a -> a) -> Ctxt a -> Ctxt a
updateDef n f ctxt
= let ds = lookupCtxtName n ctxt in
foldr (\ (n, t) c -> addDef n (f t) c) ctxt ds
toAlist :: Ctxt a -> [(Name, a)]
toAlist ctxt = let allns = map snd (Map.toList ctxt) in
concatMap (Map.toList) allns
addAlist :: [(Name, a)] -> Ctxt a -> Ctxt a
addAlist [] ctxt = ctxt
addAlist ((n, tm) : ds) ctxt = addDef n tm (addAlist ds ctxt)
data NativeTy = IT8 | IT16 | IT32 | IT64
deriving (Show, Eq, Ord, Enum, Data, Typeable)
instance Pretty NativeTy OutputAnnotation where
pretty IT8 = text "Bits8"
pretty IT16 = text "Bits16"
pretty IT32 = text "Bits32"
pretty IT64 = text "Bits64"
data IntTy = ITFixed NativeTy | ITNative | ITBig | ITChar
deriving (Show, Eq, Ord, Data, Typeable)
intTyName :: IntTy -> String
intTyName ITNative = "Int"
intTyName ITBig = "BigInt"
intTyName (ITFixed sized) = "B" ++ show (nativeTyWidth sized)
intTyName (ITChar) = "Char"
data ArithTy = ATInt IntTy | ATFloat -- TODO: Float vectors https://github.com/idris-lang/Idris-dev/issues/1723
deriving (Show, Eq, Ord, Data, Typeable)
{-!
deriving instance NFData IntTy
deriving instance NFData NativeTy
deriving instance NFData ArithTy
!-}
instance Pretty ArithTy OutputAnnotation where
pretty (ATInt ITNative) = text "Int"
pretty (ATInt ITBig) = text "BigInt"
pretty (ATInt ITChar) = text "Char"
pretty (ATInt (ITFixed n)) = pretty n
pretty ATFloat = text "Float"
nativeTyWidth :: NativeTy -> Int
nativeTyWidth IT8 = 8
nativeTyWidth IT16 = 16
nativeTyWidth IT32 = 32
nativeTyWidth IT64 = 64
{-# DEPRECATED intTyWidth "Non-total function, use nativeTyWidth and appropriate casing" #-}
intTyWidth :: IntTy -> Int
intTyWidth (ITFixed n) = nativeTyWidth n
intTyWidth ITNative = 8 * sizeOf (0 :: Int)
intTyWidth ITChar = error "IRTS.Lang.intTyWidth: Characters have platform and backend dependent width"
intTyWidth ITBig = error "IRTS.Lang.intTyWidth: Big integers have variable width"
data Const = I Int | BI Integer | Fl Double | Ch Char | Str String
| B8 Word8 | B16 Word16 | B32 Word32 | B64 Word64
| AType ArithTy | StrType
| WorldType | TheWorld
| VoidType | Forgot
deriving (Eq, Ord, Data, Typeable)
{-!
deriving instance Binary Const
deriving instance NFData Const
!-}
isTypeConst :: Const -> Bool
isTypeConst (AType _) = True
isTypeConst StrType = True
isTypeConst WorldType = True
isTypeConst VoidType = True
isTypeConst _ = False
instance Sized Const where
size _ = 1
instance Pretty Const OutputAnnotation where
pretty (I i) = text . show $ i
pretty (BI i) = text . show $ i
pretty (Fl f) = text . show $ f
pretty (Ch c) = text . show $ c
pretty (Str s) = text s
pretty (AType a) = pretty a
pretty StrType = text "String"
pretty TheWorld = text "%theWorld"
pretty WorldType = text "prim__World"
pretty VoidType = text "Void"
pretty Forgot = text "Forgot"
pretty (B8 w) = text . show $ w
pretty (B16 w) = text . show $ w
pretty (B32 w) = text . show $ w
pretty (B64 w) = text . show $ w
-- | Determines whether the input constant represents a type
constIsType :: Const -> Bool
constIsType (I _) = False
constIsType (BI _) = False
constIsType (Fl _) = False
constIsType (Ch _) = False
constIsType (Str _) = False
constIsType (B8 _) = False
constIsType (B16 _) = False
constIsType (B32 _) = False
constIsType (B64 _) = False
constIsType _ = True
-- | Get the docstring for a Const
constDocs :: Const -> String
constDocs c@(AType (ATInt ITBig)) = "Arbitrary-precision integers"
constDocs c@(AType (ATInt ITNative)) = "Fixed-precision integers of undefined size"
constDocs c@(AType (ATInt ITChar)) = "Characters in some unspecified encoding"
constDocs c@(AType ATFloat) = "Double-precision floating-point numbers"
constDocs StrType = "Strings in some unspecified encoding"
constDocs c@(AType (ATInt (ITFixed IT8))) = "Eight bits (unsigned)"
constDocs c@(AType (ATInt (ITFixed IT16))) = "Sixteen bits (unsigned)"
constDocs c@(AType (ATInt (ITFixed IT32))) = "Thirty-two bits (unsigned)"
constDocs c@(AType (ATInt (ITFixed IT64))) = "Sixty-four bits (unsigned)"
constDocs (Fl f) = "A float"
constDocs (I i) = "A fixed-precision integer"
constDocs (BI i) = "An arbitrary-precision integer"
constDocs (Str s) = "A string of length " ++ show (length s)
constDocs (Ch c) = "A character"
constDocs (B8 w) = "The eight-bit value 0x" ++
showIntAtBase 16 intToDigit w ""
constDocs (B16 w) = "The sixteen-bit value 0x" ++
showIntAtBase 16 intToDigit w ""
constDocs (B32 w) = "The thirty-two-bit value 0x" ++
showIntAtBase 16 intToDigit w ""
constDocs (B64 w) = "The sixty-four-bit value 0x" ++
showIntAtBase 16 intToDigit w ""
constDocs prim = "Undocumented"
data Universe = NullType | UniqueType | AllTypes
deriving (Eq, Ord, Data, Typeable)
instance Show Universe where
show UniqueType = "UniqueType"
show NullType = "NullType"
show AllTypes = "AnyType"
data Raw = Var Name
| RBind Name (Binder Raw) Raw
| RApp Raw Raw
| RType
| RUType Universe
| RForce Raw
| RConstant Const
deriving (Show, Eq, Data, Typeable)
instance Sized Raw where
size (Var name) = 1
size (RBind name bind right) = 1 + size bind + size right
size (RApp left right) = 1 + size left + size right
size RType = 1
size (RUType _) = 1
size (RForce raw) = 1 + size raw
size (RConstant const) = size const
instance Pretty Raw OutputAnnotation where
pretty = text . show
{-!
deriving instance Binary Raw
deriving instance NFData Raw
!-}
data ImplicitInfo = Impl { tcinstance :: Bool }
deriving (Show, Eq, Ord, Data, Typeable)
{-!
deriving instance Binary ImplicitInfo
deriving instance NFData ImplicitInfo
!-}
-- The type parameter `b` will normally be something like `TT Name` or just
-- `Raw`. We do not make a type-level distinction between TT terms that happen
-- to be TT types and TT terms that are not TT types.
-- | All binding forms are represented in a uniform fashion. This type only represents
-- the types of bindings (and their values, if any); the attached identifiers are part
-- of the 'Bind' constructor for the 'TT' type.
data Binder b = Lam { binderTy :: !b {-^ type annotation for bound variable-}}
| Pi { binderImpl :: Maybe ImplicitInfo,
binderTy :: !b,
binderKind :: !b }
{-^ A binding that occurs in a function type expression, e.g. @(x:Int) -> ...@
The 'binderImpl' flag says whether it was a scoped implicit
(i.e. forall bound) in the high level Idris, but otherwise
has no relevance in TT. -}
| Let { binderTy :: !b,
binderVal :: b {-^ value for bound variable-}}
-- ^ A binding that occurs in a @let@ expression
| NLet { binderTy :: !b,
binderVal :: b }
| Hole { binderTy :: !b}
| GHole { envlen :: Int,
localnames :: [Name],
binderTy :: !b}
| Guess { binderTy :: !b,
binderVal :: b }
| PVar { binderTy :: !b }
-- ^ A pattern variable
| PVTy { binderTy :: !b }
deriving (Show, Eq, Ord, Functor, Foldable, Traversable, Data, Typeable)
{-!
deriving instance Binary Binder
deriving instance NFData Binder
!-}
instance Sized a => Sized (Binder a) where
size (Lam ty) = 1 + size ty
size (Pi _ ty _) = 1 + size ty
size (Let ty val) = 1 + size ty + size val
size (NLet ty val) = 1 + size ty + size val
size (Hole ty) = 1 + size ty
size (GHole _ _ ty) = 1 + size ty
size (Guess ty val) = 1 + size ty + size val
size (PVar ty) = 1 + size ty
size (PVTy ty) = 1 + size ty
fmapMB :: Monad m => (a -> m b) -> Binder a -> m (Binder b)
fmapMB f (Let t v) = liftM2 Let (f t) (f v)
fmapMB f (NLet t v) = liftM2 NLet (f t) (f v)
fmapMB f (Guess t v) = liftM2 Guess (f t) (f v)
fmapMB f (Lam t) = liftM Lam (f t)
fmapMB f (Pi i t k) = liftM2 (Pi i) (f t) (f k)
fmapMB f (Hole t) = liftM Hole (f t)
fmapMB f (GHole i ns t) = liftM (GHole i ns) (f t)
fmapMB f (PVar t) = liftM PVar (f t)
fmapMB f (PVTy t) = liftM PVTy (f t)
raw_apply :: Raw -> [Raw] -> Raw
raw_apply f [] = f
raw_apply f (a : as) = raw_apply (RApp f a) as
raw_unapply :: Raw -> (Raw, [Raw])
raw_unapply t = ua [] t where
ua args (RApp f a) = ua (a:args) f
ua args t = (t, args)
-- WELL TYPED TERMS ---------------------------------------------------------
-- | Universe expressions for universe checking
data UExp = UVar Int -- ^ universe variable
| UVal Int -- ^ explicit universe level
deriving (Eq, Ord, Data, Typeable)
{-!
deriving instance NFData UExp
!-}
instance Sized UExp where
size _ = 1
instance Show UExp where
show (UVar x) | x < 26 = [toEnum (x + fromEnum 'a')]
| otherwise = toEnum ((x `mod` 26) + fromEnum 'a') : show (x `div` 26)
show (UVal x) = show x
-- show (UMax l r) = "max(" ++ show l ++ ", " ++ show r ++")"
-- | Universe constraints
data UConstraint = ULT UExp UExp -- ^ Strictly less than
| ULE UExp UExp -- ^ Less than or equal to
deriving (Eq, Ord, Data, Typeable)
data ConstraintFC = ConstraintFC { uconstraint :: UConstraint,
ufc :: FC }
deriving (Show, Data, Typeable)
instance Eq ConstraintFC where
x == y = uconstraint x == uconstraint y
instance Ord ConstraintFC where
compare x y = compare (uconstraint x) (uconstraint y)
instance Show UConstraint where
show (ULT x y) = show x ++ " < " ++ show y
show (ULE x y) = show x ++ " <= " ++ show y
type UCs = (Int, [UConstraint])
data NameType = Bound
| Ref
| DCon {nt_tag :: Int, nt_arity :: Int, nt_unique :: Bool} -- ^ Data constructor
| TCon {nt_tag :: Int, nt_arity :: Int} -- ^ Type constructor
deriving (Show, Ord, Data, Typeable)
{-!
deriving instance Binary NameType
deriving instance NFData NameType
!-}
instance Sized NameType where
size _ = 1
instance Pretty NameType OutputAnnotation where
pretty = text . show
instance Eq NameType where
Bound == Bound = True
Ref == Ref = True
DCon _ a _ == DCon _ b _ = (a == b) -- ignore tag
TCon _ a == TCon _ b = (a == b) -- ignore tag
_ == _ = False
data AppStatus n = Complete
| MaybeHoles
| Holes [n]
deriving (Eq, Ord, Functor, Data, Typeable, Show)
-- | Terms in the core language. The type parameter is the type of
-- identifiers used for bindings and explicit named references;
-- usually we use @TT 'Name'@.
data TT n = P NameType n (TT n) -- ^ named references with type
-- (P for "Parameter", motivated by McKinna and Pollack's
-- Pure Type Systems Formalized)
| V !Int -- ^ a resolved de Bruijn-indexed variable
| Bind n !(Binder (TT n)) (TT n) -- ^ a binding
| App (AppStatus n) !(TT n) (TT n) -- ^ function, function type, arg
| Constant Const -- ^ constant
| Proj (TT n) !Int -- ^ argument projection; runtime only
-- (-1) is a special case for 'subtract one from BI'
| Erased -- ^ an erased term
| Impossible -- ^ special case for totality checking
| TType UExp -- ^ the type of types at some level
| UType Universe -- ^ Uniqueness type universe (disjoint from TType)
deriving (Ord, Functor, Data, Typeable)
{-!
deriving instance Binary TT
deriving instance NFData TT
!-}
class TermSize a where
termsize :: Name -> a -> Int
instance TermSize a => TermSize [a] where
termsize n [] = 0
termsize n (x : xs) = termsize n x + termsize n xs
instance TermSize (TT Name) where
termsize n (P _ n' _)
| n' == n = 1000000 -- recursive => really big
| otherwise = 1
termsize n (V _) = 1
-- for `Bind` terms, we can erroneously declare a term
-- "recursive => really big" if the name of the bound
-- variable is the same as the name we're using
-- So generate a different name in that case.
termsize n (Bind n' (Let t v) sc)
= let rn = if n == n' then sMN 0 "noname" else n in
termsize rn v + termsize rn sc
termsize n (Bind n' b sc)
= let rn = if n == n' then sMN 0 "noname" else n in
termsize rn sc
termsize n (App _ f a) = termsize n f + termsize n a
termsize n (Proj t i) = termsize n t
termsize n _ = 1
instance Sized Universe where
size u = 1
instance Sized a => Sized (TT a) where
size (P name n trm) = 1 + size name + size n + size trm
size (V v) = 1
size (Bind nm binder bdy) = 1 + size nm + size binder + size bdy
size (App _ l r) = 1 + size l + size r
size (Constant c) = size c
size Erased = 1
size (TType u) = 1 + size u
size (Proj a _) = 1 + size a
size Impossible = 1
size (UType u) = 1 + size u
instance Pretty a o => Pretty (TT a) o where
pretty _ = text "test"
type EnvTT n = [(n, Binder (TT n))]
data Datatype n = Data { d_typename :: n,
d_typetag :: Int,
d_type :: (TT n),
d_unique :: Bool,
d_cons :: [(n, TT n)] }
deriving (Show, Functor, Eq)
-- | Data declaration options
data DataOpt = Codata -- ^ Set if the the data-type is coinductive
| DefaultEliminator -- ^ Set if an eliminator should be generated for data type
| DefaultCaseFun -- ^ Set if a case function should be generated for data type
| DataErrRev
deriving (Show, Eq)
type DataOpts = [DataOpt]
data TypeInfo = TI { con_names :: [Name],
codata :: Bool,
data_opts :: DataOpts,
param_pos :: [Int],
mutual_types :: [Name] }
deriving Show
{-!
deriving instance Binary TypeInfo
deriving instance NFData TypeInfo
!-}
instance Eq n => Eq (TT n) where
(==) (P xt x _) (P yt y _) = x == y
(==) (V x) (V y) = x == y
(==) (Bind _ xb xs) (Bind _ yb ys) = xs == ys && xb == yb
(==) (App _ fx ax) (App _ fy ay) = ax == ay && fx == fy
(==) (TType _) (TType _) = True -- deal with constraints later
(==) (Constant x) (Constant y) = x == y
(==) (Proj x i) (Proj y j) = x == y && i == j
(==) Erased _ = True
(==) _ Erased = True
(==) _ _ = False
-- * A few handy operations on well typed terms:
-- | A term is injective iff it is a data constructor, type constructor,
-- constant, the type Type, pi-binding, or an application of an injective
-- term.
isInjective :: TT n -> Bool
isInjective (P (DCon _ _ _) _ _) = True
isInjective (P (TCon _ _) _ _) = True
isInjective (Constant _) = True
isInjective (TType x) = True
isInjective (Bind _ (Pi _ _ _) sc) = True
isInjective (App _ f a) = isInjective f
isInjective _ = False
-- | Count the number of instances of a de Bruijn index in a term
vinstances :: Int -> TT n -> Int
vinstances i (V x) | i == x = 1
vinstances i (App _ f a) = vinstances i f + vinstances i a
vinstances i (Bind x b sc) = instancesB b + vinstances (i + 1) sc
where instancesB (Let t v) = vinstances i v
instancesB _ = 0
vinstances i t = 0
-- | Replace the outermost (index 0) de Bruijn variable with the given term
instantiate :: TT n -> TT n -> TT n
instantiate e = subst 0 where
subst i (P nt x ty) = P nt x (subst i ty)
subst i (V x) | i == x = e
subst i (Bind x b sc) = Bind x (fmap (subst i) b) (subst (i+1) sc)
subst i (App s f a) = App s (subst i f) (subst i a)
subst i (Proj x idx) = Proj (subst i x) idx
subst i t = t
-- | As 'instantiate', but also decrement the indices of all de Bruijn variables
-- remaining in the term, so that there are no more references to the variable
-- that has been substituted.
substV :: TT n -> TT n -> TT n
substV x tm = dropV 0 (instantiate x tm) where
dropV i (P nt x ty) = P nt x (dropV i ty)
dropV i (V x) | x > i = V (x - 1)
| otherwise = V x
dropV i (Bind x b sc) = Bind x (fmap (dropV i) b) (dropV (i+1) sc)
dropV i (App s f a) = App s (dropV i f) (dropV i a)
dropV i (Proj x idx) = Proj (dropV i x) idx
dropV i t = t
-- | Replace all non-free de Bruijn references in the given term with references
-- to the name of their binding.
explicitNames :: TT n -> TT n
explicitNames (Bind x b sc) = let b' = fmap explicitNames b in
Bind x b'
(explicitNames (instantiate
(P Bound x (binderTy b')) sc))
explicitNames (App s f a) = App s (explicitNames f) (explicitNames a)
explicitNames (Proj x idx) = Proj (explicitNames x) idx
explicitNames t = t
-- | Replace references to the given 'Name'-like id with references to
-- de Bruijn index 0.
pToV :: Eq n => n -> TT n -> TT n
pToV n = pToV' n 0
pToV' n i (P _ x _) | n == x = V i
pToV' n i (Bind x b sc)
-- We can assume the inner scope has been pToVed already, so continue to
-- resolve names from the *outer* scope which may happen to have the same id.
| n == x = Bind x (fmap (pToV' n i) b) sc
| otherwise = Bind x (fmap (pToV' n i) b) (pToV' n (i+1) sc)
pToV' n i (App s f a) = App s (pToV' n i f) (pToV' n i a)
pToV' n i (Proj t idx) = Proj (pToV' n i t) idx
pToV' n i t = t
-- increase de Bruijn indices, as if a binder has been added
addBinder :: TT n -> TT n
addBinder t = ab 0 t
where
ab top (V i) | i >= top = V (i + 1)
| otherwise = V i
ab top (Bind x b sc) = Bind x (fmap (ab top) b) (ab (top + 1) sc)
ab top (App s f a) = App s (ab top f) (ab top a)
ab top (Proj t idx) = Proj (ab top t) idx
ab top t = t
-- | Convert several names. First in the list comes out as V 0
pToVs :: Eq n => [n] -> TT n -> TT n
pToVs ns tm = pToVs' ns tm 0 where
pToVs' [] tm i = tm
pToVs' (n:ns) tm i = pToV' n i (pToVs' ns tm (i+1))
-- | Replace de Bruijn indices in the given term with explicit references to
-- the names of the bindings they refer to. It is an error if the given term
-- contains free de Bruijn indices.
vToP :: TT n -> TT n
vToP = vToP' [] where
vToP' env (V i) = let (n, b) = (env !! i) in
P Bound n (binderTy b)
vToP' env (Bind n b sc) = let b' = fmap (vToP' env) b in
Bind n b' (vToP' ((n, b'):env) sc)
vToP' env (App s f a) = App s (vToP' env f) (vToP' env a)
vToP' env t = t
-- | Replace every non-free reference to the name of a binding in
-- the given term with a de Bruijn index.
finalise :: Eq n => TT n -> TT n
finalise (Bind x b sc) = Bind x (fmap finalise b) (pToV x (finalise sc))
finalise (App s f a) = App s (finalise f) (finalise a)
finalise t = t
-- Once we've finished checking everything about a term we no longer need
-- the type on the 'P' so erase it so save memory
pEraseType :: TT n -> TT n
pEraseType (P nt t _) = P nt t Erased
pEraseType (App s f a) = App s (pEraseType f) (pEraseType a)
pEraseType (Bind n b sc) = Bind n (fmap pEraseType b) (pEraseType sc)
pEraseType t = t
-- | As 'instantiate', but in addition to replacing @'V' 0@,
-- replace references to the given 'Name'-like id.
subst :: Eq n => n {-^ The id to replace -} ->
TT n {-^ The replacement term -} ->
TT n {-^ The term to replace in -} ->
TT n
-- subst n v tm = instantiate v (pToV n tm)
subst n v tm = fst $ subst' 0 tm
where
-- keep track of updates to save allocations - this is a big win on
-- large terms in particular
-- ('Maybe' would be neater here, but >>= is not the right combinator.
-- Feel free to tidy up, as long as it still saves allocating when no
-- substitution happens...)
subst' i (V x) | i == x = (v, True)
subst' i (P _ x _) | n == x = (v, True)
subst' i t@(P nt x ty)
= let (ty', ut) = subst' i ty in
if ut then (P nt x ty', True) else (t, False)
subst' i t@(Bind x b sc) | x /= n
= let (b', ub) = substB' i b
(sc', usc) = subst' (i+1) sc in
if ub || usc then (Bind x b' sc', True) else (t, False)
subst' i t@(App s f a) = let (f', uf) = subst' i f
(a', ua) = subst' i a in
if uf || ua then (App s f' a', True) else (t, False)
subst' i t@(Proj x idx) = let (x', u) = subst' i x in
if u then (Proj x' idx, u) else (t, False)
subst' i t = (t, False)
substB' i b@(Let t v) = let (t', ut) = subst' i t
(v', uv) = subst' i v in
if ut || uv then (Let t' v', True)
else (b, False)
substB' i b@(Guess t v) = let (t', ut) = subst' i t
(v', uv) = subst' i v in
if ut || uv then (Guess t' v', True)
else (b, False)
substB' i b = let (ty', u) = subst' i (binderTy b) in
if u then (b { binderTy = ty' }, u) else (b, False)
-- If there are no Vs in the term (i.e. in proof state)
psubst :: Eq n => n -> TT n -> TT n -> TT n
psubst n v tm = s' 0 tm where
s' i (V x) | x > i = V (x - 1)
| x == i = v
| otherwise = V x
s' i (P _ x _) | n == x = v
s' i (Bind x b sc) | n == x = Bind x (fmap (s' i) b) sc
| otherwise = Bind x (fmap (s' i) b) (s' (i+1) sc)
s' i (App st f a) = App st (s' i f) (s' i a)
s' i (Proj t idx) = Proj (s' i t) idx
s' i t = t
-- | As 'subst', but takes a list of (name, substitution) pairs instead
-- of a single name and substitution
substNames :: Eq n => [(n, TT n)] -> TT n -> TT n
substNames [] t = t
substNames ((n, tm) : xs) t = subst n tm (substNames xs t)
-- | Replaces all terms equal (in the sense of @(==)@) to
-- the old term with the new term.
substTerm :: Eq n => TT n {-^ Old term -} ->
TT n {-^ New term -} ->
TT n {-^ template term -}
-> TT n
substTerm old new = st where
st t | t == old = new
st (App s f a) = App s (st f) (st a)
st (Bind x b sc) = Bind x (fmap st b) (st sc)
st t = t
-- | Return number of occurrences of V 0 or bound name i the term
occurrences :: Eq n => n -> TT n -> Int
occurrences n t = execState (no' 0 t) 0
where
no' i (V x) | i == x = do num <- get; put (num + 1)
no' i (P Bound x _) | n == x = do num <- get; put (num + 1)
no' i (Bind n b sc) = do noB' i b; no' (i+1) sc
where noB' i (Let t v) = do no' i t; no' i v
noB' i (Guess t v) = do no' i t; no' i v
noB' i b = no' i (binderTy b)
no' i (App _ f a) = do no' i f; no' i a
no' i (Proj x _) = no' i x
no' i _ = return ()
-- | Returns true if V 0 and bound name n do not occur in the term
noOccurrence :: Eq n => n -> TT n -> Bool
noOccurrence n t = no' 0 t
where
no' i (V x) = not (i == x)
no' i (P Bound x _) = not (n == x)
no' i (Bind n b sc) = noB' i b && no' (i+1) sc
where noB' i (Let t v) = no' i t && no' i v
noB' i (Guess t v) = no' i t && no' i v
noB' i b = no' i (binderTy b)
no' i (App _ f a) = no' i f && no' i a
no' i (Proj x _) = no' i x
no' i _ = True
-- | Returns all names used free in the term
freeNames :: Eq n => TT n -> [n]
freeNames t = nub $ freeNames' t
where
freeNames' (P _ n _) = [n]
freeNames' (Bind n (Let t v) sc) = freeNames' v ++ (freeNames' sc \\ [n])
++ freeNames' t
freeNames' (Bind n b sc) = freeNames' (binderTy b) ++ (freeNames' sc \\ [n])
freeNames' (App _ f a) = freeNames' f ++ freeNames' a
freeNames' (Proj x i) = freeNames' x
freeNames' _ = []
-- | Return the arity of a (normalised) type
arity :: TT n -> Int
arity (Bind n (Pi _ t _) sc) = 1 + arity sc
arity _ = 0
-- | Deconstruct an application; returns the function and a list of arguments
unApply :: TT n -> (TT n, [TT n])
unApply t = ua [] t where
ua args (App _ f a) = ua (a:args) f
ua args t = (t, args)
-- | Returns a term representing the application of the first argument
-- (a function) to every element of the second argument.
mkApp :: TT n -> [TT n] -> TT n
mkApp f [] = f
mkApp f (a:as) = mkApp (App MaybeHoles f a) as
unList :: Term -> Maybe [Term]
unList tm = case unApply tm of
(nil, [_]) -> Just []
(cons, ([_, x, xs])) ->
do rest <- unList xs
return $ x:rest
(f, args) -> Nothing
-- | Hard-code a heuristic maximum term size, to prevent attempts to
-- serialize or force infinite or just gigantic terms
termSmallerThan :: Int -> Term -> Bool
termSmallerThan x tm | x <= 0 = False
termSmallerThan x (P _ _ ty) = termSmallerThan (x-1) ty
termSmallerThan x (Bind _ _ tm) = termSmallerThan (x-1) tm
termSmallerThan x (App _ f a) = termSmallerThan (x-1) f && termSmallerThan (x-1) a
termSmallerThan x (Proj tm _) = termSmallerThan (x-1) tm
termSmallerThan x (V i) = True
termSmallerThan x (Constant c) = True
termSmallerThan x Erased = True
termSmallerThan x Impossible = True
termSmallerThan x (TType u) = True
termSmallerThan x (UType u) = True
-- | Cast a 'TT' term to a 'Raw' value, discarding universe information and
-- the types of named references and replacing all de Bruijn indices
-- with the corresponding name. It is an error if there are free de
-- Bruijn indices.
forget :: TT Name -> Raw
forget tm = forgetEnv [] tm
safeForget :: TT Name -> Maybe Raw
safeForget tm = safeForgetEnv [] tm
forgetEnv :: [Name] -> TT Name -> Raw
forgetEnv env tm = case safeForgetEnv env tm of
Just t' -> t'
Nothing -> error $ "Scope error in " ++ show tm ++ show env
safeForgetEnv :: [Name] -> TT Name -> Maybe Raw
safeForgetEnv env (P _ n _) = Just $ Var n
safeForgetEnv env (V i) | i < length env = Just $ Var (env !! i)
| otherwise = Nothing
safeForgetEnv env (Bind n b sc)
= do let n' = uniqueName n env
b' <- safeForgetEnvB env b
sc' <- safeForgetEnv (n':env) sc
Just $ RBind n' b' sc'
where safeForgetEnvB env (Let t v) = liftM2 Let (safeForgetEnv env t)
(safeForgetEnv env v)
safeForgetEnvB env (Guess t v) = liftM2 Guess (safeForgetEnv env t)
(safeForgetEnv env v)
safeForgetEnvB env b = do ty' <- safeForgetEnv env (binderTy b)
Just $ fmap (\_ -> ty') b
safeForgetEnv env (App _ f a) = liftM2 RApp (safeForgetEnv env f) (safeForgetEnv env a)
safeForgetEnv env (Constant c) = Just $ RConstant c
safeForgetEnv env (TType i) = Just RType
safeForgetEnv env (UType u) = Just $ RUType u
safeForgetEnv env Erased = Just $ RConstant Forgot
safeForgetEnv env (Proj tm i) = error "Don't know how to forget a projection"
safeForgetEnv env Impossible = error "Don't know how to forget Impossible"
-- | Introduce a 'Bind' into the given term for each element of the
-- given list of (name, binder) pairs.
bindAll :: [(n, Binder (TT n))] -> TT n -> TT n
bindAll [] t = t
bindAll ((n, b) : bs) t = Bind n b (bindAll bs t)
-- | Like 'bindAll', but the 'Binder's are 'TT' terms instead.
-- The first argument is a function to map @TT@ terms to @Binder@s.
-- This function might often be something like 'Lam', which directly
-- constructs a @Binder@ from a @TT@ term.
bindTyArgs :: (TT n -> Binder (TT n)) -> [(n, TT n)] -> TT n -> TT n
bindTyArgs b xs = bindAll (map (\ (n, ty) -> (n, b ty)) xs)
-- | Return a list of pairs of the names of the outermost 'Pi'-bound
-- variables in the given term, together with their types.
getArgTys :: TT n -> [(n, TT n)]
getArgTys (Bind n (PVar _) sc) = getArgTys sc
getArgTys (Bind n (PVTy _) sc) = getArgTys sc
getArgTys (Bind n (Pi _ t _) sc) = (n, t) : getArgTys sc
getArgTys _ = []
getRetTy :: TT n -> TT n
getRetTy (Bind n (PVar _) sc) = getRetTy sc
getRetTy (Bind n (PVTy _) sc) = getRetTy sc
getRetTy (Bind n (Pi _ _ _) sc) = getRetTy sc
getRetTy sc = sc
uniqueNameFrom :: [Name] -> [Name] -> Name
uniqueNameFrom [] hs = uniqueName (nextName (sUN "x")) hs
uniqueNameFrom (s : supply) hs
| s `elem` hs = uniqueNameFrom supply hs
| otherwise = s
uniqueName :: Name -> [Name] -> Name
uniqueName n hs | n `elem` hs = uniqueName (nextName n) hs
| otherwise = n
uniqueNameSet :: Name -> Set Name -> Name
uniqueNameSet n hs | n `member` hs = uniqueNameSet (nextName n) hs
| otherwise = n
uniqueBinders :: [Name] -> TT Name -> TT Name
uniqueBinders ns = ubSet (fromList ns) where
ubSet ns (Bind n b sc)
= let n' = uniqueNameSet n ns
ns' = insert n' ns in
Bind n' (fmap (ubSet ns') b) (ubSet ns' sc)
ubSet ns (App s f a) = App s (ubSet ns f) (ubSet ns a)
ubSet ns t = t
nextName :: Name -> Name
nextName (NS x s) = NS (nextName x) s
nextName (MN i n) = MN (i+1) n
nextName (UN x) = let (num', nm') = T.span isDigit (T.reverse x)
nm = T.reverse nm'
num = readN (T.reverse num') in
UN (nm `T.append` txt (show (num+1)))
where
readN x | not (T.null x) = read (T.unpack x)
readN x = 0
nextName (SN x) = SN (nextName' x)
where
nextName' (WhereN i f x) = WhereN i f (nextName x)
nextName' (WithN i n) = WithN i (nextName n)
nextName' (InstanceN n ns) = InstanceN (nextName n) ns
nextName' (ParentN n ns) = ParentN (nextName n) ns
nextName' (CaseN n) = CaseN (nextName n)
nextName' (ElimN n) = ElimN (nextName n)
nextName' (MethodN n) = MethodN (nextName n)
nextName' (InstanceCtorN n) = InstanceCtorN (nextName n)
nextName' (MetaN parent meta) = MetaN parent (nextName meta)
nextName NErased = NErased
nextName (SymRef i) = error "Can't generate a name from a symbol reference"
type Term = TT Name
type Type = Term
type Env = EnvTT Name
-- | an environment with de Bruijn indices 'normalised' so that they all refer to
-- this environment
newtype WkEnvTT n = Wk (EnvTT n)
type WkEnv = WkEnvTT Name
instance (Eq n, Show n) => Show (TT n) where
show t = showEnv [] t
itBitsName IT8 = "Bits8"
itBitsName IT16 = "Bits16"
itBitsName IT32 = "Bits32"
itBitsName IT64 = "Bits64"
instance Show Const where
show (I i) = show i
show (BI i) = show i
show (Fl f) = show f
show (Ch c) = show c
show (Str s) = show s
show (B8 x) = show x
show (B16 x) = show x
show (B32 x) = show x
show (B64 x) = show x
show (AType ATFloat) = "Double"
show (AType (ATInt ITBig)) = "Integer"
show (AType (ATInt ITNative)) = "Int"
show (AType (ATInt ITChar)) = "Char"
show (AType (ATInt (ITFixed it))) = itBitsName it
show TheWorld = "prim__TheWorld"
show WorldType = "prim__WorldType"
show StrType = "String"
show VoidType = "Void"
show Forgot = "Forgot"
showEnv :: (Eq n, Show n) => EnvTT n -> TT n -> String
showEnv env t = showEnv' env t False
showEnvDbg env t = showEnv' env t True
prettyEnv :: Env -> Term -> Doc OutputAnnotation
prettyEnv env t = prettyEnv' env t False
where
prettyEnv' env t dbg = prettySe 10 env t dbg
bracket outer inner p
| inner > outer = lparen <> p <> rparen
| otherwise = p
prettySe p env (P nt n t) debug =
pretty n <+>
if debug then
lbracket <+> pretty nt <+> colon <+> prettySe 10 env t debug <+> rbracket
else
empty
prettySe p env (V i) debug
| i < length env =
if debug then
text . show . fst $ env!!i
else
lbracket <+> text (show i) <+> rbracket
| otherwise = text "unbound" <+> text (show i) <+> text "!"
prettySe p env (Bind n b@(Pi _ t _) sc) debug
| noOccurrence n sc && not debug =
bracket p 2 $ prettySb env n b debug <> prettySe 10 ((n, b):env) sc debug
prettySe p env (Bind n b sc) debug =
bracket p 2 $ prettySb env n b debug <> prettySe 10 ((n, b):env) sc debug
prettySe p env (App _ f a) debug =
bracket p 1 $ prettySe 1 env f debug <+> prettySe 0 env a debug
prettySe p env (Proj x i) debug =
prettySe 1 env x debug <+> text ("!" ++ show i)
prettySe p env (Constant c) debug = pretty c
prettySe p env Erased debug = text "[_]"
prettySe p env (TType i) debug = text "Type" <+> (text . show $ i)
prettySe p env Impossible debug = text "Impossible"
prettySe p env (UType u) debug = text (show u)
-- Render a `Binder` and its name
prettySb env n (Lam t) = prettyB env "Ξ»" "=>" n t
prettySb env n (Hole t) = prettyB env "?defer" "." n t
prettySb env n (GHole _ _ t) = prettyB env "?gdefer" "." n t
prettySb env n (Pi _ t _) = prettyB env "(" ") ->" n t
prettySb env n (PVar t) = prettyB env "pat" "." n t
prettySb env n (PVTy t) = prettyB env "pty" "." n t
prettySb env n (Let t v) = prettyBv env "let" "in" n t v
prettySb env n (NLet t v) = prettyBv env "nlet" "in" n t v
prettySb env n (Guess t v) = prettyBv env "??" "in" n t v
-- Use `op` and `sc` to delimit `n` (a binding name) and its type
-- declaration
-- e.g. "Ξ»x : Int =>" for the Lam case
prettyB env op sc n t debug =
text op <> pretty n <+> colon <+> prettySe 10 env t debug <> text sc
-- Like `prettyB`, but handle the bindings that have values in addition
-- to names and types
prettyBv env op sc n t v debug =
text op <> pretty n <+> colon <+> prettySe 10 env t debug <+> text "=" <+>
prettySe 10 env v debug <> text sc
showEnv' env t dbg = se 10 env t where
se p env (P nt n t) = show n
++ if dbg then "{" ++ show nt ++ " : " ++ se 10 env t ++ "}" else ""
se p env (V i) | i < length env && i >= 0
= (show $ fst $ env!!i) ++
if dbg then "{" ++ show i ++ "}" else ""
| otherwise = "!!V " ++ show i ++ "!!"
se p env (Bind n b@(Pi (Just _) t k) sc)
= bracket p 2 $ sb env n b ++ se 10 ((n,b):env) sc
se p env (Bind n b@(Pi _ t k) sc)
| noOccurrence n sc && not dbg = bracket p 2 $ se 1 env t ++ arrow k ++ se 10 ((n,b):env) sc
where arrow (TType _) = " -> "
arrow u = " [" ++ show u ++ "] -> "
se p env (Bind n b sc) = bracket p 2 $ sb env n b ++ se 10 ((n,b):env) sc
se p env (App _ f a) = bracket p 1 $ se 1 env f ++ " " ++ se 0 env a
se p env (Proj x i) = se 1 env x ++ "!" ++ show i
se p env (Constant c) = show c
se p env Erased = "[__]"
se p env Impossible = "[impossible]"
se p env (TType i) = "Type " ++ show i
se p env (UType u) = show u
sb env n (Lam t) = showb env "\\ " " => " n t
sb env n (Hole t) = showb env "? " ". " n t
sb env n (GHole i ns t) = showb env "?defer " ". " n t
sb env n (Pi (Just _) t _) = showb env "{" "} -> " n t
sb env n (Pi _ t _) = showb env "(" ") -> " n t
sb env n (PVar t) = showb env "pat " ". " n t
sb env n (PVTy t) = showb env "pty " ". " n t
sb env n (Let t v) = showbv env "let " " in " n t v
sb env n (NLet t v) = showbv env "nlet " " in " n t v
sb env n (Guess t v) = showbv env "?? " " in " n t v
showb env op sc n t = op ++ show n ++ " : " ++ se 10 env t ++ sc
showbv env op sc n t v = op ++ show n ++ " : " ++ se 10 env t ++ " = " ++
se 10 env v ++ sc
bracket outer inner str | inner > outer = "(" ++ str ++ ")"
| otherwise = str
-- | Check whether a term has any hole bindings in it - impure if so
pureTerm :: TT Name -> Bool
pureTerm (App _ f a) = pureTerm f && pureTerm a
pureTerm (Bind n b sc) = notClassName n && pureBinder b && pureTerm sc where
pureBinder (Hole _) = False
pureBinder (Guess _ _) = False
pureBinder (Let t v) = pureTerm t && pureTerm v
pureBinder t = pureTerm (binderTy t)
notClassName (MN _ c) | c == txt "class" = False
notClassName _ = True
pureTerm _ = True
-- | Weaken a term by adding i to each de Bruijn index (i.e. lift it over i bindings)
weakenTm :: Int -> TT n -> TT n
weakenTm i t = wk i 0 t
where wk i min (V x) | x >= min = V (i + x)
wk i m (App s f a) = App s (wk i m f) (wk i m a)
wk i m (Bind x b sc) = Bind x (wkb i m b) (wk i (m + 1) sc)
wk i m t = t
wkb i m t = fmap (wk i m) t
-- | Weaken an environment so that all the de Bruijn indices are correct according
-- to the latest bound variable
weakenEnv :: EnvTT n -> EnvTT n
weakenEnv env = wk (length env - 1) env
where wk i [] = []
wk i ((n, b) : bs) = (n, weakenTmB i b) : wk (i - 1) bs
weakenTmB i (Let t v) = Let (weakenTm i t) (weakenTm i v)
weakenTmB i (Guess t v) = Guess (weakenTm i t) (weakenTm i v)
weakenTmB i t = t { binderTy = weakenTm i (binderTy t) }
-- | Weaken every term in the environment by the given amount
weakenTmEnv :: Int -> EnvTT n -> EnvTT n
weakenTmEnv i = map (\ (n, b) -> (n, fmap (weakenTm i) b))
-- | Gather up all the outer 'PVar's and 'Hole's in an expression and reintroduce
-- them in a canonical order
orderPats :: Term -> Term
orderPats tm = op [] tm
where
op [] (App s f a) = App s f (op [] a) -- for Infer terms
op ps (Bind n (PVar t) sc) = op ((n, PVar t) : ps) sc
op ps (Bind n (Hole t) sc) = op ((n, Hole t) : ps) sc
op ps (Bind n (Pi i t k) sc) = op ((n, Pi i t k) : ps) sc
op ps sc = bindAll (sortP ps) sc
sortP ps = pick [] (reverse ps)
pick acc [] = reverse acc
pick acc ((n, t) : ps) = pick (insert n t acc) ps
insert n t [] = [(n, t)]
insert n t ((n',t') : ps)
| n `elem` (refsIn (binderTy t') ++
concatMap refsIn (map (binderTy . snd) ps))
= (n', t') : insert n t ps
| otherwise = (n,t):(n',t'):ps
refsIn :: TT Name -> [Name]
refsIn (P _ n _) = [n]
refsIn (Bind n b t) = nub $ nb b ++ refsIn t
where nb (Let t v) = nub (refsIn t) ++ nub (refsIn v)
nb (Guess t v) = nub (refsIn t) ++ nub (refsIn v)
nb t = refsIn (binderTy t)
refsIn (App s f a) = nub (refsIn f ++ refsIn a)
refsIn _ = []
-- Make sure all the pattern bindings are as far out as possible
liftPats :: Term -> Term
liftPats tm = let (tm', ps) = runState (getPats tm) [] in
orderPats $ bindPats (reverse ps) tm'
where
bindPats [] tm = tm
bindPats ((n, t):ps) tm
| n `notElem` map fst ps = Bind n (PVar t) (bindPats ps tm)
| otherwise = bindPats ps tm
getPats :: Term -> State [(Name, Type)] Term
getPats (Bind n (PVar t) sc) = do ps <- get
put ((n, t) : ps)
getPats sc
getPats (Bind n (Guess t v) sc) = do t' <- getPats t
v' <- getPats v
sc' <- getPats sc
return (Bind n (Guess t' v') sc')
getPats (Bind n (Let t v) sc) = do t' <- getPats t
v' <- getPats v
sc' <- getPats sc
return (Bind n (Let t' v') sc')
getPats (Bind n (Pi i t k) sc) = do t' <- getPats t
k' <- getPats k
sc' <- getPats sc
return (Bind n (Pi i t' k') sc')
getPats (Bind n (Lam t) sc) = do t' <- getPats t
sc' <- getPats sc
return (Bind n (Lam t') sc')
getPats (Bind n (Hole t) sc) = do t' <- getPats t
sc' <- getPats sc
return (Bind n (Hole t') sc')
getPats (App s f a) = do f' <- getPats f
a' <- getPats a
return (App s f' a')
getPats t = return t
allTTNames :: Eq n => TT n -> [n]
allTTNames = nub . allNamesIn
where allNamesIn (P _ n _) = [n]
allNamesIn (Bind n b t) = [n] ++ nb b ++ allNamesIn t
where nb (Let t v) = allNamesIn t ++ allNamesIn v
nb (Guess t v) = allNamesIn t ++ allNamesIn v
nb t = allNamesIn (binderTy t)
allNamesIn (App _ f a) = allNamesIn f ++ allNamesIn a
allNamesIn _ = []
-- | Pretty-print a term
pprintTT :: [Name] -- ^ The bound names (for highlighting and de Bruijn indices)
-> TT Name -- ^ The term to be printed
-> Doc OutputAnnotation
pprintTT bound tm = pp startPrec bound tm
where
startPrec = 0
appPrec = 10
pp p bound (P Bound n ty) = annotate (AnnBoundName n False) (text $ show n)
pp p bound (P nt n ty) = annotate (AnnName n Nothing Nothing Nothing)
(text $ show n)
pp p bound (V i)
| i < length bound = let n = bound !! i
in annotate (AnnBoundName n False) (text $ show n)
| otherwise = text ("{{{V" ++ show i ++ "}}}")
pp p bound (Bind n b sc) = ppb p bound n b $
pp startPrec (n:bound) sc
pp p bound (App _ tm1 tm2) =
bracket p appPrec . group . hang 2 $
pp appPrec bound tm1 <> line <>
pp (appPrec + 1) bound tm2
pp p bound (Constant c) = annotate (AnnConst c) (text (show c))
pp p bound (Proj tm i) =
lparen <> pp startPrec bound tm <> rparen <>
text "!" <> text (show i)
pp p bound Erased = text "<<<erased>>>"
pp p bound Impossible = text "<<<impossible>>>"
pp p bound (TType ue) = annotate (AnnType "Type" "The type of types") $
text "Type"
pp p bound (UType u) = text (show u)
ppb p bound n (Lam ty) sc =
bracket p startPrec . group . align . hang 2 $
text "Ξ»" <+> bindingOf n False <+> text "." <> line <> sc
ppb p bound n (Pi _ ty k) sc =
bracket p startPrec . group . align $
lparen <> (bindingOf n False) <+> colon <+>
(group . align) (pp startPrec bound ty) <>
rparen <+> mkArrow k <> line <> sc
where mkArrow (UType UniqueType) = text "β΄"
mkArrow (UType NullType) = text "β₯"
mkArrow _ = text "β"
ppb p bound n (Let ty val) sc =
bracket p startPrec . group . align $
(group . hang 2) (annotate AnnKeyword (text "let") <+>
bindingOf n False <+> colon <+>
pp startPrec bound ty <+>
text "=" <> line <>
pp startPrec bound val) <> line <>
(group . hang 2) (annotate AnnKeyword (text "in") <+> sc)
ppb p bound n (NLet ty val) sc =
bracket p startPrec . group . align $
(group . hang 2) (annotate AnnKeyword (text "nlet") <+>
bindingOf n False <+> colon <+>
pp startPrec bound ty <+>
text "=" <> line <>
pp startPrec bound val) <> line <>
(group . hang 2) (annotate AnnKeyword (text "in") <+> sc)
ppb p bound n (Hole ty) sc =
bracket p startPrec . group . align . hang 2 $
text "?" <+> bindingOf n False <+> text "." <> line <> sc
ppb p bound n (GHole _ _ ty) sc =
bracket p startPrec . group . align . hang 2 $
text "ΒΏ" <+> bindingOf n False <+> text "." <> line <> sc
ppb p bound n (Guess ty val) sc =
bracket p startPrec . group . align . hang 2 $
text "?" <> bindingOf n False <+>
text "β" <+> pp startPrec bound val <+>
text "." <> line <> sc
ppb p bound n (PVar ty) sc =
bracket p startPrec . group . align . hang 2 $
annotate AnnKeyword (text "pat") <+>
bindingOf n False <+> colon <+> pp startPrec bound ty <+>
text "." <> line <>
sc
ppb p bound n (PVTy ty) sc =
bracket p startPrec . group . align . hang 2 $
annotate AnnKeyword (text "patTy") <+>
bindingOf n False <+> colon <+> pp startPrec bound ty <+>
text "." <> line <>
sc
bracket outer inner doc
| outer > inner = lparen <> doc <> rparen
| otherwise = doc
-- | Pretty-print a raw term.
pprintRaw :: [Name] -- ^ Bound names, for highlighting
-> Raw -- ^ The term to pretty-print
-> Doc OutputAnnotation
pprintRaw bound (Var n) =
enclose lparen rparen . group . align . hang 2 $
(text "Var") <$> annotate (if n `elem` bound
then AnnBoundName n False
else AnnName n Nothing Nothing Nothing)
(text $ show n)
pprintRaw bound (RBind n b body) =
enclose lparen rparen . group . align . hang 2 $
vsep [ text "RBind"
, annotate (AnnBoundName n False) (text $ show n)
, ppb b
, pprintRaw (n:bound) body]
where
ppb (Lam ty) = enclose lparen rparen . group . align . hang 2 $
text "Lam" <$> pprintRaw bound ty
ppb (Pi _ ty k) = enclose lparen rparen . group . align . hang 2 $
vsep [text "Pi", pprintRaw bound ty, pprintRaw bound k]
ppb (Let ty v) = enclose lparen rparen . group . align . hang 2 $
vsep [text "Let", pprintRaw bound ty, pprintRaw bound v]
ppb (NLet ty v) = enclose lparen rparen . group . align . hang 2 $
vsep [text "NLet", pprintRaw bound ty, pprintRaw bound v]
ppb (Hole ty) = enclose lparen rparen . group . align . hang 2 $
text "Hole" <$> pprintRaw bound ty
ppb (GHole _ _ ty) = enclose lparen rparen . group . align . hang 2 $
text "GHole" <$> pprintRaw bound ty
ppb (Guess ty v) = enclose lparen rparen . group . align . hang 2 $
vsep [text "Guess", pprintRaw bound ty, pprintRaw bound v]
ppb (PVar ty) = enclose lparen rparen . group . align . hang 2 $
text "PVar" <$> pprintRaw bound ty
ppb (PVTy ty) = enclose lparen rparen . group . align . hang 2 $
text "PVTy" <$> pprintRaw bound ty
pprintRaw bound (RApp f x) =
enclose lparen rparen . group . align . hang 2 . vsep $
[text "RApp", pprintRaw bound f, pprintRaw bound x]
pprintRaw bound RType = text "RType"
pprintRaw bound (RUType u) = enclose lparen rparen . group . align . hang 2 $
text "RUType" <$> text (show u)
pprintRaw bound (RForce r) =
enclose lparen rparen . group . align . hang 2 $
vsep [text "RForce", pprintRaw bound r]
pprintRaw bound (RConstant c) =
enclose lparen rparen . group . align . hang 2 $
vsep [text "RConstant", annotate (AnnConst c) (text (show c))]
-- | Pretty-printer helper for the binding site of a name
bindingOf :: Name -- ^^ the bound name
-> Bool -- ^^ whether the name is implicit
-> Doc OutputAnnotation
bindingOf n imp = annotate (AnnBoundName n imp) (text (show n))
| Enamex/Idris-dev | src/Idris/Core/TT.hs | Haskell | bsd-3-clause | 71,139 |
module L01.Optional where
-- class Optional<A> {
-- Optional(A a) {} // Full
-- Optional() {} // Empty
-- }
data Optional a = Full a | Empty deriving (Eq, Show)
mapOptional :: (a -> b) -> Optional a -> Optional b
mapOptional _ Empty = Empty
mapOptional f (Full a) = Full (f a)
bindOptional :: Optional a -> (a -> Optional b) -> Optional b
bindOptional Empty _ = Empty
bindOptional (Full a) f = f a
(??) :: Optional a -> a -> a
Empty ?? d = d
Full a ?? _ = a
(<+>) :: Optional a -> Optional a -> Optional a
Empty <+> o = o
k <+> _ = k
| juretta/course | src/L01/Optional.hs | Haskell | bsd-3-clause | 559 |
module LetIn1 where
--A definition can be demoted to the local 'where' binding of a friend declaration,
--if it is only used by this friend declaration.
--Demoting a definition narrows down the scope of the definition.
--In this example, demote the local 'pow' to 'sq'
--This example also aims to test the demoting a local declaration in 'let'.
sumSquares x y = let sq 0=0
sq z=z^pow
pow=2
in sq x + sq y
anotherFun 0 y = sq y
where sq x = x^2
| mpickering/ghc-exactprint | tests/examples/transform/LetIn1.hs | Haskell | bsd-3-clause | 517 |
module Jhc.Prim.Bits where
-- this declares the built in unboxed types.
-- no code is brought in by this module, it just
-- brings the names into scope, so it is okay to
-- have platform specific definitions here.
-- The CTYPE of the raw types is declared in src/DataConstructors.hs
data Bits1_ :: #
data Bits8_ :: #
data Bits16_ :: #
data Bits32_ :: #
data Bits64_ :: #
data Bits128_ :: #
data BitsPtr_ :: #
data BitsMax_ :: #
data Float16_ :: #
data Float32_ :: #
data Float64_ :: #
data Float80_ :: #
data Float128_ :: #
data FloatMax_ :: #
data Complex_ :: # -> #
-- these newtypes exist to modify the
-- calling convention and provide hints as
-- to the use of the types.
newtype {-# CTYPE "HsPtr" #-} Addr_ = Addr_ BitsPtr_
newtype {-# CTYPE "HsFunPtr" #-} FunAddr_ = FunAddr_ BitsPtr_
newtype {-# CTYPE "bool" #-} Bool_ = Bool_ Bits16_
newtype {-# CTYPE "wchar_t" #-} Char_ = Char_ Bits32_
-- type aliases to help document whether signed or unsigned
-- uses are intended, they have no effect other than helping
-- convey intent to someone reading the code.
type Word_ = Bits32_
type Int_ = Bits32_
type AddrLen_ = (# Addr_, Word_ #)
| hvr/jhc | lib/jhc-prim/Jhc/Prim/Bits.hs | Haskell | mit | 1,176 |
<?xml version="1.0" encoding="UTF-8"?><!DOCTYPE helpset PUBLIC "-//Sun Microsystems Inc.//DTD JavaHelp HelpSet Version 2.0//EN" "http://java.sun.com/products/javahelp/helpset_2_0.dtd">
<helpset version="2.0" xml:lang="fr-FR">
<title>Eval Villain Add-On</title>
<maps>
<homeID>evalvillain</homeID>
<mapref location="map.jhm"/>
</maps>
<view>
<name>TOC</name>
<label>Contents</label>
<type>org.zaproxy.zap.extension.help.ZapTocView</type>
<data>toc.xml</data>
</view>
<view>
<name>Index</name>
<label>Index</label>
<type>javax.help.IndexView</type>
<data>index.xml</data>
</view>
<view>
<name>Search</name>
<label>Search</label>
<type>javax.help.SearchView</type>
<data engine="com.sun.java.help.search.DefaultSearchEngine">
JavaHelpSearch
</data>
</view>
<view>
<name>Favorites</name>
<label>Favorites</label>
<type>javax.help.FavoritesView</type>
</view>
</helpset> | kingthorin/zap-extensions | addOns/evalvillain/src/main/javahelp/org/zaproxy/addon/evalvillain/resources/help_fr_FR/helpset_fr_FR.hs | Haskell | apache-2.0 | 972 |
{-# LANGUAGE GADTs #-}
-----------------------------------------------------------------------------
--
-- Debugging data
--
-- Association of debug data on the Cmm level, with methods to encode it in
-- event log format for later inclusion in profiling event logs.
--
-----------------------------------------------------------------------------
module Debug (
DebugBlock(..), dblIsEntry,
UnwindTable, UnwindExpr(..),
cmmDebugGen,
cmmDebugLabels,
cmmDebugLink,
debugToMap
) where
import BlockId ( blockLbl )
import CLabel
import Cmm
import CmmUtils
import CoreSyn
import FastString ( nilFS, mkFastString )
import Module
import Outputable
import PprCore ()
import PprCmmExpr ( pprExpr )
import SrcLoc
import Util
import Compiler.Hoopl
import Data.Maybe
import Data.List ( minimumBy, nubBy )
import Data.Ord ( comparing )
import qualified Data.Map as Map
-- | Debug information about a block of code. Ticks scope over nested
-- blocks.
data DebugBlock =
DebugBlock
{ dblProcedure :: !Label -- ^ Entry label of containing proc
, dblLabel :: !Label -- ^ Hoopl label
, dblCLabel :: !CLabel -- ^ Output label
, dblHasInfoTbl :: !Bool -- ^ Has an info table?
, dblParent :: !(Maybe DebugBlock)
-- ^ The parent of this proc. See Note [Splitting DebugBlocks]
, dblTicks :: ![CmmTickish] -- ^ Ticks defined in this block
, dblSourceTick
:: !(Maybe CmmTickish) -- ^ Best source tick covering block
, dblPosition :: !(Maybe Int) -- ^ Output position relative to
-- other blocks. @Nothing@ means
-- the block was optimized out
, dblUnwind :: !UnwindTable -- ^ Unwind information
, dblBlocks :: ![DebugBlock] -- ^ Nested blocks
}
-- | Is this the entry block?
dblIsEntry :: DebugBlock -> Bool
dblIsEntry blk = dblProcedure blk == dblLabel blk
instance Outputable DebugBlock where
ppr blk = (if dblProcedure blk == dblLabel blk
then text "proc "
else if dblHasInfoTbl blk
then text "pp-blk "
else text "blk ") <>
ppr (dblLabel blk) <+> parens (ppr (dblCLabel blk)) <+>
(maybe empty ppr (dblSourceTick blk)) <+>
(maybe (text "removed") ((text "pos " <>) . ppr)
(dblPosition blk)) <+>
pprUwMap (dblUnwind blk) $$
(if null (dblBlocks blk) then empty else ppr (dblBlocks blk))
where pprUw (g, expr) = ppr g <> char '=' <> ppr expr
pprUwMap = braces . hsep . punctuate comma . map pprUw . Map.toList
-- | Intermediate data structure holding debug-relevant context information
-- about a block.
type BlockContext = (CmmBlock, RawCmmDecl, UnwindTable)
-- | Extract debug data from a group of procedures. We will prefer
-- source notes that come from the given module (presumably the module
-- that we are currently compiling).
cmmDebugGen :: ModLocation -> RawCmmGroup -> [DebugBlock]
cmmDebugGen modLoc decls = map (blocksForScope Nothing) topScopes
where
blockCtxs :: Map.Map CmmTickScope [BlockContext]
blockCtxs = blockContexts decls
-- Analyse tick scope structure: Each one is either a top-level
-- tick scope, or the child of another.
(topScopes, childScopes)
= splitEithers $ map (\a -> findP a a) $ Map.keys blockCtxs
findP tsc GlobalScope = Left tsc -- top scope
findP tsc scp | scp' `Map.member` blockCtxs = Right (scp', tsc)
| otherwise = findP tsc scp'
where -- Note that we only following the left parent of
-- combined scopes. This loses us ticks, which we will
-- recover by copying ticks below.
scp' | SubScope _ scp' <- scp = scp'
| CombinedScope scp' _ <- scp = scp'
| otherwise = panic "findP impossible"
scopeMap = foldr (uncurry insertMulti) Map.empty childScopes
-- This allows us to recover ticks that we lost by flattening
-- the graph. Basically, if the parent is A but the child is
-- CBA, we know that there is no BA, because it would have taken
-- priority - but there might be a B scope, with ticks that
-- would not be associated with our child anymore. Note however
-- that there might be other childs (DB), which we have to
-- filter out.
--
-- We expect this to be called rarely, which is why we are not
-- trying too hard to be efficient here. In many cases we won't
-- have to construct blockCtxsU in the first place.
ticksToCopy :: CmmTickScope -> [CmmTickish]
ticksToCopy (CombinedScope scp s) = go s
where go s | scp `isTickSubScope` s = [] -- done
| SubScope _ s' <- s = ticks ++ go s'
| CombinedScope s1 s2 <- s = ticks ++ go s1 ++ go s2
| otherwise = panic "ticksToCopy impossible"
where ticks = bCtxsTicks $ fromMaybe [] $ Map.lookup s blockCtxs
ticksToCopy _ = []
bCtxsTicks = concatMap (blockTicks . fstOf3)
-- Finding the "best" source tick is somewhat arbitrary -- we
-- select the first source span, while preferring source ticks
-- from the same source file. Furthermore, dumps take priority
-- (if we generated one, we probably want debug information to
-- refer to it).
bestSrcTick = minimumBy (comparing rangeRating)
rangeRating (SourceNote span _)
| srcSpanFile span == thisFile = 1
| otherwise = 2 :: Int
rangeRating note = pprPanic "rangeRating" (ppr note)
thisFile = maybe nilFS mkFastString $ ml_hs_file modLoc
-- Returns block tree for this scope as well as all nested
-- scopes. Note that if there are multiple blocks in the (exact)
-- same scope we elect one as the "branch" node and add the rest
-- as children.
blocksForScope :: Maybe CmmTickish -> CmmTickScope -> DebugBlock
blocksForScope cstick scope = mkBlock True (head bctxs)
where bctxs = fromJust $ Map.lookup scope blockCtxs
nested = fromMaybe [] $ Map.lookup scope scopeMap
childs = map (mkBlock False) (tail bctxs) ++
map (blocksForScope stick) nested
mkBlock top (block, prc, unwind)
= DebugBlock { dblProcedure = g_entry graph
, dblLabel = label
, dblCLabel = case info of
Just (Statics infoLbl _) -> infoLbl
Nothing
| g_entry graph == label -> entryLbl
| otherwise -> blockLbl label
, dblHasInfoTbl = isJust info
, dblParent = Nothing
, dblTicks = ticks
, dblPosition = Nothing -- see cmmDebugLink
, dblUnwind = unwind
, dblSourceTick = stick
, dblBlocks = blocks
}
where (CmmProc infos entryLbl _ graph) = prc
label = entryLabel block
info = mapLookup label infos
blocks | top = seqList childs childs
| otherwise = []
-- A source tick scopes over all nested blocks. However
-- their source ticks might take priority.
isSourceTick SourceNote {} = True
isSourceTick _ = False
-- Collect ticks from all blocks inside the tick scope.
-- We attempt to filter out duplicates while we're at it.
ticks = nubBy (flip tickishContains) $
bCtxsTicks bctxs ++ ticksToCopy scope
stick = case filter isSourceTick ticks of
[] -> cstick
sticks -> Just $! bestSrcTick (sticks ++ maybeToList cstick)
-- | Build a map of blocks sorted by their tick scopes
--
-- This involves a pre-order traversal, as we want blocks in rough
-- control flow order (so ticks have a chance to be sorted in the
-- right order). We also use this opportunity to have blocks inherit
-- unwind information from their predecessor blocks where it is
-- lacking.
blockContexts :: RawCmmGroup -> Map.Map CmmTickScope [BlockContext]
blockContexts decls = Map.map reverse $ foldr walkProc Map.empty decls
where walkProc CmmData{} m = m
walkProc prc@(CmmProc _ _ _ graph) m
| mapNull blocks = m
| otherwise = snd $ walkBlock prc entry Map.empty (emptyLbls, m)
where blocks = toBlockMap graph
entry = [mapFind (g_entry graph) blocks]
emptyLbls = setEmpty :: LabelSet
walkBlock _ [] _ c = c
walkBlock prc (block:blocks) unwind (visited, m)
| lbl `setMember` visited
= walkBlock prc blocks unwind (visited, m)
| otherwise
= walkBlock prc blocks unwind $
walkBlock prc succs unwind'
(lbl `setInsert` visited,
insertMulti scope (block, prc, unwind') m)
where CmmEntry lbl scope = firstNode block
unwind' = extractUnwind block `Map.union` unwind
(CmmProc _ _ _ graph) = prc
succs = map (flip mapFind (toBlockMap graph))
(successors (lastNode block))
mapFind = mapFindWithDefault (error "contextTree: block not found!")
insertMulti :: Ord k => k -> a -> Map.Map k [a] -> Map.Map k [a]
insertMulti k v = Map.insertWith (const (v:)) k [v]
cmmDebugLabels :: (i -> Bool) -> GenCmmGroup d g (ListGraph i) -> [Label]
cmmDebugLabels isMeta nats = seqList lbls lbls
where -- Find order in which procedures will be generated by the
-- back-end (that actually matters for DWARF generation).
--
-- Note that we might encounter blocks that are missing or only
-- consist of meta instructions -- we will declare them missing,
-- which will skip debug data generation without messing up the
-- block hierarchy.
lbls = map blockId $ filter (not . allMeta) $ concatMap getBlocks nats
getBlocks (CmmProc _ _ _ (ListGraph bs)) = bs
getBlocks _other = []
allMeta (BasicBlock _ instrs) = all isMeta instrs
-- | Sets position fields in the debug block tree according to native
-- generated code.
cmmDebugLink :: [Label] -> [DebugBlock] -> [DebugBlock]
cmmDebugLink labels blocks = map link blocks
where blockPos :: LabelMap Int
blockPos = mapFromList $ flip zip [0..] labels
link block = block { dblPosition = mapLookup (dblLabel block) blockPos
, dblBlocks = map link (dblBlocks block)
}
-- | Converts debug blocks into a label map for easier lookups
debugToMap :: [DebugBlock] -> LabelMap DebugBlock
debugToMap = mapUnions . map go
where go b = mapInsert (dblLabel b) b $ mapUnions $ map go (dblBlocks b)
-- | Maps registers to expressions that yield their "old" values
-- further up the stack. Most interesting for the stack pointer Sp,
-- but might be useful to document saved registers, too.
type UnwindTable = Map.Map GlobalReg UnwindExpr
-- | Expressions, used for unwind information
data UnwindExpr = UwConst Int -- ^ literal value
| UwReg GlobalReg Int -- ^ register plus offset
| UwDeref UnwindExpr -- ^ pointer dereferencing
| UwPlus UnwindExpr UnwindExpr
| UwMinus UnwindExpr UnwindExpr
| UwTimes UnwindExpr UnwindExpr
deriving (Eq)
instance Outputable UnwindExpr where
pprPrec _ (UwConst i) = ppr i
pprPrec _ (UwReg g 0) = ppr g
pprPrec p (UwReg g x) = pprPrec p (UwPlus (UwReg g 0) (UwConst x))
pprPrec _ (UwDeref e) = char '*' <> pprPrec 3 e
pprPrec p (UwPlus e0 e1) | p <= 0
= pprPrec 0 e0 <> char '+' <> pprPrec 0 e1
pprPrec p (UwMinus e0 e1) | p <= 0
= pprPrec 1 e0 <> char '-' <> pprPrec 1 e1
pprPrec p (UwTimes e0 e1) | p <= 1
= pprPrec 2 e0 <> char '*' <> pprPrec 2 e1
pprPrec _ other = parens (pprPrec 0 other)
extractUnwind :: CmmBlock -> UnwindTable
extractUnwind b = go $ blockToList mid
where (_, mid, _) = blockSplit b
go :: [CmmNode O O] -> UnwindTable
go [] = Map.empty
go (x : xs) = case x of
CmmUnwind g so -> Map.insert g (toUnwindExpr so) $! go xs
CmmTick {} -> go xs
_other -> Map.empty
-- TODO: Unwind statements after actual instructions
-- | Conversion of Cmm expressions to unwind expressions. We check for
-- unsupported operator usages and simplify the expression as far as
-- possible.
toUnwindExpr :: CmmExpr -> UnwindExpr
toUnwindExpr (CmmLit (CmmInt i _)) = UwConst (fromIntegral i)
toUnwindExpr (CmmRegOff (CmmGlobal g) i) = UwReg g i
toUnwindExpr (CmmReg (CmmGlobal g)) = UwReg g 0
toUnwindExpr (CmmLoad e _) = UwDeref (toUnwindExpr e)
toUnwindExpr e@(CmmMachOp op [e1, e2]) =
case (op, toUnwindExpr e1, toUnwindExpr e2) of
(MO_Add{}, UwReg r x, UwConst y) -> UwReg r (x + y)
(MO_Sub{}, UwReg r x, UwConst y) -> UwReg r (x - y)
(MO_Add{}, UwConst x, UwReg r y) -> UwReg r (x + y)
(MO_Add{}, UwConst x, UwConst y) -> UwConst (x + y)
(MO_Sub{}, UwConst x, UwConst y) -> UwConst (x - y)
(MO_Mul{}, UwConst x, UwConst y) -> UwConst (x * y)
(MO_Add{}, u1, u2 ) -> UwPlus u1 u2
(MO_Sub{}, u1, u2 ) -> UwMinus u1 u2
(MO_Mul{}, u1, u2 ) -> UwTimes u1 u2
_otherwise -> pprPanic "Unsupported operator in unwind expression!"
(pprExpr e)
toUnwindExpr e
= pprPanic "Unsupported unwind expression!" (ppr e)
| mcschroeder/ghc | compiler/cmm/Debug.hs | Haskell | bsd-3-clause | 14,390 |
{-# LANGUAGE CPP #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
-- |
-- Module : Diagrams.Lens
-- Copyright : (c) 2013 Michael Sloan
-- License : BSD-style (see LICENSE)
-- Maintainer : Michael Sloan <mgsloan at gmail>
--
-- This module provides utilities for using "Control.Lens" with diagrams.
module Diagrams.Lens
(
-- * Diagrams.BoundingBox
_corners
-- * Diagrams.Core.Types
, _location
-- * Diagrams.Located
, _Loc
-- * Diagrams.Parametric
-- , _arcLength
-- * Diagrams.Segment
, _mkFixedSeg
, _straight
, _bezier3
-- * Diagrams.Trail
, _lineSegments
) where
#if __GLASGOW_HASKELL__ < 710
import Control.Applicative
import Data.Foldable
#endif
import Diagrams.BoundingBox
import Diagrams.Prelude
-- * Diagrams.BoundingBox
-- | A traversal that either has 0 (empty box) or 2 points. These points are
-- the lower and upper corners, respectively.
_corners
:: (Additive v', Foldable v', Ord n')
=> Traversal (BoundingBox v n) (BoundingBox v' n') (Point v n) (Point v' n')
_corners f (getCorners -> Just (l, t)) = fromCorners <$> f l <*> f t
_corners _ _ = pure emptyBox
-- * Diagrams.Core.Types
-- | Gets or set the 'location' of a 'Subdiagram'.
_location
:: (HasLinearMap v, Metric v, OrderedField n)
=> Lens' (Subdiagram b v n m) (Point v n)
--TODO: Is this correct??
_location = lens location (flip Diagrams.Prelude.moveTo)
-- * Diagrams.Located
_Loc :: Iso (Located a) (Located a') (Point (V a) (N a), a) (Point (V a') (N a'), a')
_Loc = iso viewLoc (uncurry $ flip Diagrams.Prelude.at)
-- * Diagrams.Parametric
{- TODO: requires 'arcLengthFromParam'
_arcLength
:: HasArcLength p => N p -> p -> Iso' (N p) (N p)
_arcLength eps curve
= iso' (arcLengthFromParam eps curve) (arcLengthToParam eps curve)
-}
-- * Diagrams.Segment
_mkFixedSeg
:: (Additive v, Additive v', Num n, Num n')
=> Iso
(Located (Segment Closed v n))
(Located (Segment Closed v' n'))
(FixedSegment v n)
(FixedSegment v' n')
_mkFixedSeg = iso mkFixedSeg fromFixedSeg
-- | Prism that constructs linear segments. Can also destruct them, if the
-- segment is Linear.
_straight :: Prism' (Segment Closed v n) (v n)
_straight = prism' straight fromStraight
where
fromStraight :: Segment c v n -> Maybe (v n)
fromStraight (Linear (OffsetClosed x)) = Just x
fromStraight _ = Nothing
-- | Prism that constructs cubic bezier segments. Can also destruct them, if
-- segment is a 'Cubic'.
_bezier3 :: Prism' (Segment Closed v n) (v n, v n, v n)
_bezier3 = prism' (\(c1, c2, c3) -> bezier3 c1 c2 c3) fromBezier3
where
fromBezier3 :: Segment c v n -> Maybe (v n, v n, v n)
fromBezier3 (Cubic c1 c2 (OffsetClosed c3)) = Just (c1, c2, c3)
fromBezier3 _ = Nothing
-- * Diagrams.Trail
_lineSegments
:: (Metric v', OrderedField n')
=> Iso
(Trail' Line v n) (Trail' Line v' n')
[Segment Closed v n] [Segment Closed v' n']
_lineSegments = iso lineSegments lineFromSegments
| wherkendell/diagrams-contrib | src/Diagrams/Lens.hs | Haskell | bsd-3-clause | 3,351 |
import Control.Exception as E
-- This test shows what hpc can really do.
main = do
print ("Hello")
foo "Hello"
E.catch (print (badCase 22 44))
(\ e -> print (e :: E.ErrorCall))
E.catch (print (badCase 22 (error "Foo")))
(\ e -> print (e :: E.ErrorCall))
E.catch (print "Bark")
(\ e -> print (e :: E.ErrorCall))
(_,_) <- return $ ("Hello","World")
return ()
() <- return ()
t <- case () of
_ | otherwoz -> return "Hello"
_ -> error "Bad Thing Happened"
t <- case () of
_ | otherwise -> return "Hello"
_ -> error "Bad Thing Happened"
t <- case () of
_ | otherwise
, False -> error "Bad Thing Happened"
_ -> return "Hello"
print t
print foo2
foo x = do
print x
return ()
unused_ a = a
badCase :: Int -> Int -> Int
badCase a b =
if a > 100
then error "badCase"
else if a > 1000
then 1
else badCase (a + 1) (b - 1)
foo2 = (1,2, if True then 3 else 4)
otherwoz = True
| ttuegel/hpc | tests/function/tough.hs | Haskell | bsd-3-clause | 1,059 |
{-# LANGUAGE DataKinds, PolyKinds, RankNTypes, GADTs #-}
module T7481 where
import Data.Kind (Type)
import Data.Proxy
data D a where
D1 :: a -> D a
D2 :: (a~Int) => D a
D3 :: forall k (a::k) b. Proxy a -> D b
data Foo :: D Type -> Type
| sdiehl/ghc | testsuite/tests/polykinds/T7481.hs | Haskell | bsd-3-clause | 247 |
module Test20 where
f y xs = [x | x <- xs] + y
| SAdams601/HaRe | old/testing/refacSlicing/Test20_TokOut.hs | Haskell | bsd-3-clause | 49 |
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
module Web.Slack.WebAPI
( SlackConfig(..)
, makeSlackCall
-- * Methods
, rtm_start
, chat_postMessage
, reactions_add_message
) where
import Control.Lens hiding ((??))
import Control.Monad.Except
import Data.Aeson
import Data.Aeson.Lens
import qualified Data.ByteString.Lazy as BL
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Network.Wreq as W
import Web.Slack.Types
-- | Configuration options needed to connect to the Slack API
data SlackConfig = SlackConfig
{ _slackApiToken :: String -- ^ API Token for Bot
} deriving (Show)
makeLenses ''SlackConfig
makeSlackCall
:: (MonadError T.Text m, MonadIO m)
=> SlackConfig
-> String
-> (W.Options -> W.Options)
-> m Value
makeSlackCall conf method setArgs = do
let url = "https://slack.com/api/" ++ method
let setToken = W.param "token" .~ [T.pack (conf ^. slackApiToken)]
let opts = W.defaults & setToken & setArgs
rawResp <- liftIO $ W.getWith opts url
resp <- rawResp ^? W.responseBody . _Value ?? "Couldn't parse response"
case resp ^? key "ok" . _Bool of
Just True -> return resp
Just False -> throwError $ resp ^. key "error" . _String
Nothing -> throwError "Couldn't parse key 'ok' from response"
-------------------------------------------------------------------------------
-- Methods
-- See https://api.slack.com/methods for the docs.
rtm_start
:: (MonadError T.Text m, MonadIO m)
=> SlackConfig
-> m (T.Text, SlackSession)
rtm_start conf = do
resp <- makeSlackCall conf "rtm.start" id
url <- resp ^? key "url" . _String ?? "rtm_start: No url!"
sessionInfo <- fromJSON' resp
return (url, sessionInfo)
chat_postMessage
:: (MonadError T.Text m, MonadIO m)
=> SlackConfig
-> ChannelId
-> T.Text
-> [Attachment]
-> m ()
chat_postMessage conf (Id cid) msg as =
void $ makeSlackCall conf "chat.postMessage" $
(W.param "channel" .~ [cid]) .
(W.param "text" .~ [msg]) .
(W.param "attachments" .~ [encode' as]) .
(W.param "as_user" .~ ["true"])
reactions_add_message
:: (MonadError T.Text m, MonadIO m)
=> SlackConfig
-> ChannelId
-> T.Text
-> SlackTimeStamp
-> m ()
reactions_add_message conf (Id cid) emoji timestamp = do
void $ makeSlackCall conf "reactions.add" $
(W.param "name" .~ [emoji]) .
(W.param "channel" .~ [cid]) .
(W.param "timestamp" .~ [encode' timestamp])
-------------------------------------------------------------------------------
-- Helpers
encode' :: ToJSON a => a -> T.Text
encode' = T.decodeUtf8 . BL.toStrict . encode
fromJSON' :: (FromJSON a, MonadError T.Text m) => Value -> m a
fromJSON' x = case fromJSON x of
Error e -> throwError (T.pack e)
Success r -> return r
-- | Like '(??)' from Control.Error, but a bit more general and with the
-- right precedence.
infixl 7 ??
(??) :: MonadError e m => Maybe a -> e -> m a
x ?? e = maybe (throwError e) return x
| mpickering/slack-api | src/Web/Slack/WebAPI.hs | Haskell | mit | 3,177 |
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ViewPatterns #-}
module ChaostreffScheduler where
import Protolude
import Data.Time
import Data.List ((!!), groupBy, concat, head)
import Lektor
import Event
import AppCfg
import Git
schedule :: (MonadIO m, MonadReader AppCfg m) => m ()
schedule = do
gitCheckout
scheduleChaostreffs
scheduleTechEvents
-- scheduleFreiesHacken
schedule3DDD
gitCommitAndPush
-- |
scheduleChaostreffs :: (MonadIO m, MonadReader AppCfg m) => m ()
scheduleChaostreffs = do
template <- loadLektorEventTemplate "contents-chaostreff.tmpl"
dates <- chaostreffDates
let events = fmap (\d -> template { eventTitle = "Chaostreff", eventDate = d }) dates
mapM_ createLektorCalendarEntry events
-- |
scheduleTechEvents :: (MonadIO m, MonadReader AppCfg m) => m ()
scheduleTechEvents = do
template <- loadLektorEventTemplate "contents-tech-event.tmpl"
dates <- techEventDates
let events = fmap (\d -> template { eventTitle = "Tech-Event", eventDate = d }) dates
mapM_ createLektorCalendarEntry events
scheduleFreiesHacken :: (MonadIO m, MonadReader AppCfg m) => m ()
scheduleFreiesHacken = do
template <- loadLektorEventTemplate "contents-freies-hacken.tmpl"
dates <- freiesHackenDates
let events = fmap (\d -> template { eventTitle = "Freies Hacken", eventDate = d }) dates
mapM_ createLektorCalendarEntry events
schedule3DDD :: (MonadIO m, MonadReader AppCfg m) => m ()
schedule3DDD = do
template <- loadLektorEventTemplate "contents-3ddd.tmpl"
dates <- dddDates
let events = fmap (\d -> template { eventTitle = "3D-Drucker-Donnerstag", eventDate = d }) dates
mapM_ createLektorCalendarEntry events
-- |
-- >>> runReaderT chaostreffDates $ AppCfg "" "" NoPushChanges (Year 2019) (Month 2) (MonthCount 2)
-- [2019-02-05 20:00:00 UTC,2019-02-19 20:00:00 UTC,2019-03-05 20:00:00 UTC,2019-03-19 20:00:00 UTC]
chaostreffDates :: (MonadIO m, MonadReader AppCfg m) => m [UTCTime]
chaostreffDates = fmap withTime . concat <$> (filterOdds . filter ((== Tuesday) . dayOfWeek)) <$$> range
where withTime d = UTCTime d (timeOfDayToTime $ TimeOfDay 20 0 0)
filterOdds = fmap snd . filter (odd . fst) . zip [1..]
-- |
-- >>> runReaderT techEventDates $ AppCfg "" "" NoPushChanges (Year 2019) (Month 1) (MonthCount 4)
-- [2019-01-05 14:00:00 UTC,2019-02-02 14:00:00 UTC,2019-03-02 14:00:00 UTC,2019-04-06 14:00:00 UTC]
techEventDates :: (MonadIO m, MonadReader AppCfg m) => m [UTCTime]
techEventDates = (withTime <$> Data.List.head . filter ((== Saturday) . dayOfWeek)) <$$> range
where withTime d = UTCTime d (timeOfDayToTime $ TimeOfDay 14 0 0)
-- | 'Freies Hacken' dates - every second (odd) month, the third saturday
freiesHackenDates :: (MonadIO m, MonadReader AppCfg m) => m [UTCTime]
freiesHackenDates = filter isOddMonth <$> (withTime . third . filter isSaturday) <$$> range
where isSaturday = (== Saturday) . dayOfWeek
third xs = xs !! 2
withTime d = UTCTime d (timeOfDayToTime $ TimeOfDay 14 0 0)
isOddMonth (toGregorian . utctDay -> (_, m, _)) = odd m
-- | '3DDD' dates - every third thursday
-- >>> runReaderT dddDates $ AppCfg "" "" NoPushChanges (Year 2021) (Month 8) (MonthCount 2)
-- [2021-08-19 20:00:00 UTC,2021-09-16 20:00:00 UTC]
dddDates :: (MonadIO m, MonadReader AppCfg m) => m [UTCTime]
dddDates = (withTime . third . filter isThursday) <$$> range
where isThursday = (== Thursday) . dayOfWeek
third xs = xs !! 2
withTime d = UTCTime d (timeOfDayToTime $ TimeOfDay 20 0 0)
(<$$>) :: (Functor f1, Functor f2) => (a -> b) -> f1 (f2 a) -> f1 (f2 b)
(<$$>) = fmap . fmap
-- | creates a range of days grouped by month depending on the given config
range :: (MonadIO m, MonadReader AppCfg m) => m [[Day]]
range = do
(Year y, Month m, MonthCount c) <- (,,) <$> asks cfgRunForYear <*> asks cfgRunForMonth <*> asks cfgMonthCount
pure $ take c $ groupByMonth $ days (fromGregorian y m 1)
where days d = d : days (addDays 1 d)
month (toGregorian -> (_, m, _)) = m
groupByMonth = groupBy (\d1 d2 -> month d1 == month d2)
| section77/chaostreff-scheduler | src/ChaostreffScheduler.hs | Haskell | mit | 4,121 |
-- Exercise 1
toDigits :: Integer -> [Integer]
toDigits 0 = []
toDigits n = toDigits (n `div` 10) ++ [n `mod` 10]
toDigitsRev :: Integer -> [Integer]
toDigitsRev 0 = []
toDigitsRev n = [n `mod` 10] ++ toDigitsRev (n `div` 10)
--Exercise 2
doubleEveryOther :: [Integer] -> [Integer]
doubleEveryOther
reverse' :: [Integer] -> [Integer]
reverse' [] = []
reverse' (x:xs) = reverse' xs ++ [x]
| diminishedprime/.org | reading-list/cis194/homework_01.hs | Haskell | mit | 393 |
module Main where
import System.Environment
import Commands
data Command = Help
|Β List
| Freeze
| Install
| Uninstall
| Error
instance Show Command where
show Help = "Help"
show List = "List"
show Freeze = "Freeze"
show Install = "Install"
show Uninstall = "Uninstall"
show Error = "Error"
getCommand :: String -> Command
getCommand "help" = Help
getCommand "list" = List
getCommand "freeze" = Freeze
getCommand "install" = Install
getCommand "uninstall" = Uninstall
getCommand _ = Error
dispatch :: Command -> [String] -> IO ()
dispatch Help = help
dispatch List = list
dispatch Freeze = freeze
dispatch Install = install
dispatch Uninstall = uninstall
dispatch _ = errorCmd
main :: IO ()
main = do
(name:args) <- getArgs
dispatch (getCommand name) args
| pepegar/vkg-haskell | src/Main.hs | Haskell | mit | 861 |
module Main (main) where
import Test.Framework (Test, defaultMain)
import qualified OptCrackerTests as OptCrackerTests
import qualified UserManagementTests as UserManagementTests
main :: IO ()
main = defaultMain testSuite
testSuite :: [Test]
testSuite = [ OptCrackerTests.suite
, UserManagementTests.suite ]
| AstralMining/astral-mining-server | test/TestMain.hs | Haskell | mit | 323 |
module Main where
import System.Environment
import System.IO
import System.Console.ANSI
import Data.Char
import Data.Maybe
import Data.List
import Data.Either
import Control.Monad
import Text.Megaparsec
import Text.Megaparsec.Expr
import Text.Megaparsec.String
import qualified Text.Megaparsec.Lexer as L
import Parse.Basics
import Parse.Expressions
import Parse.Declarations
import Parse.Statements
import Parse.Modules
main :: IO ()
main = do
args <- getArgs
let openRead a = openFile a ReadMode
handles <- mapM openRead args
contents <- mapM hGetContents handles
let parses = processFiles args contents
let unreferencedIdentifiers a = nub (declaredIdentifiers a) \\ nub (referencedIdentifiers a)
let undeclaredIdentifiers a = nub (referencedIdentifiers a) \\ nub (declaredIdentifiers a)
let good = concatMap rights $ rights parses
let bad = lefts parses ++ (concatMap lefts $ rights parses)
infoPrint "Declared identifiers that are never used (probably warnings):"
_ <- mapM_ warnPrint (map show $ unreferencedIdentifiers good)
infoPrint "-------------------------"
infoPrint "Referenced identifiers that are never declared (probably errors):"
_ <- mapM_ errorPrint (map show $ undeclaredIdentifiers good)
infoPrint "-------------------------"
infoPrint "Parse Errors"
_ <- mapM_ errorPrint $ map show bad
return ()
infoPrint a = do
_ <- setSGR [SetColor Foreground Dull White]
_ <- putStrLn a
clearToPs
errorPrint a = do
_ <- setSGR [SetColor Foreground Vivid Red]
_ <- putStrLn a
clearToPs
warnPrint a = do
_ <- setSGR [SetColor Foreground Vivid Yellow]
_ <- putStrLn a
clearToPs
clearToPs = do
setSGR [Reset]
processFiles :: [String] -> [String] -> [Either ParseError Recoverable]
processFiles a c = map (uncurry (parse parser)) $ zip a c
declaredIdentifiers :: [VerilogThing] -> [Identifier]
declaredIdentifiers a = concatMap getIdentifierDeclarations a
referencedIdentifiers :: [VerilogThing] -> [Identifier]
referencedIdentifiers a = concatMap getIdentifierUtilizations a
isDecl (VDecl _) = True
isDecl _ = False
isStatement (VStatement _) = True
isStatement _ = False
type Recoverable = [Either ParseError VerilogThing]
parser :: Parser Recoverable
parser = sc *> many (withRecovery' vmod) <* eof
simplify' a = case parse parser "" a of
Left _ -> fail "oops"
Right c -> c
simplify a = head $ simplify' a
data VerilogThing = VStatement Statement
| VDecl Declaration
| VMod VModule [RecoverableThing]
| VPreprocessor
deriving (Show, Eq)
instance GetIdentifiers VerilogThing where
getIdentifiers (VStatement a) = getIdentifiers a
getIdentifiers (VDecl a) = getIdentifiers a
getIdentifiers (VMod a b) = getIdentifiers a ++ concatMap getIdentifiers (rights b)
getIdentifierDeclarations (VStatement a) = getIdentifierDeclarations a
getIdentifierDeclarations (VDecl a) = getIdentifierDeclarations a
getIdentifierDeclarations (VMod a b) = getIdentifierDeclarations a ++ concatMap getIdentifierDeclarations (rights b)
getIdentifierUtilizations (VStatement a) = getIdentifierUtilizations a
getIdentifierUtilizations (VDecl a) = getIdentifierUtilizations a
getIdentifierUtilizations (VMod a b) = getIdentifierUtilizations a ++ concatMap getIdentifierUtilizations (rights b)
type RecoverableThing = Either ParseError VerilogThing
things :: Parser RecoverableThing
things = withRecovery' (vdecl <|> vstatement <|> vpreprocessor)
unrecoverableThings :: Parser VerilogThing
unrecoverableThings = vdecl <|> vstatement <|> vpreprocessor
vmod :: Parser VerilogThing
vmod =
do
_ <- sc
_ <- many vpreprocessor
_ <- sc
a <- parseModule
b <- manyTill things (rword "endmodule")
_ <- sc
return $ VMod a b
vdecl = wrap declaration VDecl
vstatement = wrap statement VStatement
vpreprocessor =
do
_ <- symbol "`"
_ <- manyTill anyChar eol
return VPreprocessor
commaSepStatements :: String -> Parser a -> Parser [a]
commaSepStatements a b = rword a *> b `sepBy` comma <* semicolon
| akindle/hdlint | Parse.hs | Haskell | mit | 4,229 |
{-|
Module: Y2015.D05
Description: Advent of Code Day 05 Solutions.
License: MIT
Maintainer: @tylerjl
Solutions to the day 05 set of problems for <adventofcode.com>.
-}
module Y2015.D05
( clean
, isNice
, isNicer
, thriceVoweled
, twiceRow
) where
import Y2015.Util ((<&&>))
import Data.List (group, isInfixOf)
-- |Whether a given string is "nice" per the spec.
isNicer
:: String -- ^ Test input string
-> Bool -- ^ Whether string is nice
isNicer = repeatedPair <&&> repeatedBetween
repeatedPair :: String -> Bool
repeatedPair (x:y:zs)
| [x, y] `isInfixOf` zs = True
| otherwise = repeatedPair (y : zs)
repeatedPair _ = False
repeatedBetween :: String -> Bool
repeatedBetween (x:y:z:zs)
| x == z = True
| otherwise = repeatedBetween (y : z : zs)
repeatedBetween _ = False
-- |Predicate to determine whether a given string is "nice".
isNice
:: String -- ^ Test input string.
-> Bool -- ^ Whether the given input string is nice.
isNice = clean <&&> thriceVoweled <&&> twiceRow
-- |Predicate to determine whether a string eschews forbidden strings.
clean
:: String -- ^ Input string.
-> Bool -- ^ Whether the string is clean.
clean = not . flip any forbiddenStrings . flip isInfixOf
forbiddenStrings :: [String]
forbiddenStrings = ["ab", "cd", "pq", "xy"]
-- |Predicate to determine whether a given string contains two letters
-- |in a row.
twiceRow
:: String -- ^ Input string to test.
-> Bool -- ^ Whether the given string passes the predicate.
twiceRow = any ((> 1) . length) . group
-- |Predicate to determine whether the given string contains at least three
-- |vowels.
thriceVoweled
:: String -- ^ Input string to test.
-> Bool -- ^ Whether the string passes the predicate.
thriceVoweled = (> 2) . length . filter isVowel
isVowel :: Char -> Bool
isVowel = flip elem "aeiou"
| tylerjl/adventofcode | src/Y2015/D05.hs | Haskell | mit | 1,839 |
callmin = min 9 10
callmax = max 9 10
-- These two are equivalent.
evaluate1 = succ 9 + max 5 4 + 1
evaluate2 = (succ 9) + (max 5 4) + 1
-- infix notation
divide1 = div 92 10
divide2 = 92 `div` 10 | v0lkan/learning-haskell | session-002/prefix.hs | Haskell | mit | 198 |
-- |
-- Implementation of dumb random AI
module Agent.Random (
RandomAgent
) where
import Control.Monad.State.Strict
import System.Random
import ToServer
import FromServer
import Agent
-- | Contains a generator for random moves
data RandomAgent = AS { gen :: StdGen }
instance Agent RandomAgent where
newAgent = fmap AS newStdGen
killAgent _ = return ()
stepAgent gs = StateT $ \(AS g) ->
let (m, g') = random g
in return (Move m, AS g')
| adamse/mmc2 | src/Agent/Random.hs | Haskell | mit | 460 |
-- Fibo akin
-- https://www.codewars.com/kata/5772382d509c65de7e000982
module Codewars.G964.Fibkind(comp, lengthSupUK) where
s = 1 : 1 : zipWith3 f s (tail s) [2..]
where f a b i = s !! (i - a) + s !! (i - b)
lengthSupUK :: Int -> Int -> Int
lengthSupUK n k = length . filter (>= k) . take n $ s
comp :: Int -> Int
comp n = length . filter (<0) . take (n - 1) . zipWith (-) (tail s) $ s
| gafiatulin/codewars | src/5 kyu/Fibkind.hs | Haskell | mit | 396 |
{-# LANGUAGE OverloadedStrings #-}
module Main where
import Control.Monad (replicateM)
import Control.Monad.IO.Class (liftIO)
import qualified Data.ByteString.Char8 as BC
import Data.Text.Encoding (decodeUtf8, encodeUtf8)
import qualified Data.Text.Lazy as TL
import qualified Database.Redis as R
import Network.URI (URI, parseURI)
import qualified System.Random as SR
import Web.Scotty
alphaNum :: String
alphaNum = ['A'..'Z'] ++ ['0'..'9']
randomElement :: String -> IO Char
randomElement xs = do
let maxIndex :: Int
maxIndex = length xs - 1
-- Right of arrow is IO Int, so randomDigit is Int
randomDigit <- SR.randomRIO (0, maxIndex) :: IO Int
return (xs !! randomDigit)
shortyGen :: IO String
shortyGen =
replicateM 7 (randomElement alphaNum)
saveURI :: R.Connection
-> BC.ByteString
-> BC.ByteString
-> IO (Either R.Reply R.Status)
saveURI conn shortURI uri =
R.runRedis conn $ R.set shortURI uri
getURI :: R.Connection
-> BC.ByteString
-> IO (Either R.Reply (Maybe BC.ByteString))
getURI conn shortURI = R.runRedis conn $ R.get shortURI
linkShorty :: String -> String
linkShorty shorty =
concat [ "<a href=\""
, shorty
, "\">Copy and paste your short URL</a>"
]
shortyCreated :: Show a => a -> String -> TL.Text
shortyCreated resp shawty =
TL.concat [ TL.pack (show resp)
, " shorty is: ", TL.pack (linkShorty shawty)
]
shortyAintUri :: TL.Text -> TL.Text
shortyAintUri uri =
TL.concat [ uri
, " wasn't a url, did you forget http://?"
]
shortyFound :: TL.Text -> TL.Text
shortyFound tbs =
TL.concat ["<a href=\"", tbs, "\">", tbs, "</a>"]
app :: R.Connection
-> ScottyM ()
app rConn = do
get "/" $ do
uri <- param "uri"
let parsedUri :: Maybe URI
parsedUri = parseURI (TL.unpack uri)
case parsedUri of
Just _ -> do
shawty <- liftIO shortyGen
let shorty = BC.pack shawty
uri' = encodeUtf8 (TL.toStrict uri)
resp <- liftIO (saveURI rConn shorty uri')
html (shortyCreated resp shawty)
Nothing -> text (shortyAintUri uri)
get "/:short" $ do
short <- param "short"
uri <- liftIO (getURI rConn short)
case uri of
Left reply -> text (TL.pack (show reply))
Right mbBS -> case mbBS of
Nothing -> text "uri not found"
Just bs -> html (shortyFound tbs)
where tbs :: TL.Text
tbs = TL.fromStrict (decodeUtf8 bs)
main :: IO ()
main = do
rConn <- R.connect R.defaultConnectInfo
scotty 3000 (app rConn) | JustinUnger/haskell-book | ch22/shawty.hs | Haskell | mit | 2,602 |
{-# htermination (>=) :: Ord a => a -> a -> Bool #-}
| ComputationWithBoundedResources/ara-inference | doc/tpdb_trs/Haskell/full_haskell/Prelude_GTEQ_1.hs | Haskell | mit | 53 |
import Common
-- Since I don't know how many numbers there are, any of the answers might be correct.
main = print $ scanl (+) 0 [ x | x <- [10..], sum [ product [1..y] | y <- (toDigits x) ] == x]
| lekto/haskell | Project-Euler-Solutions/problem0034.hs | Haskell | mit | 197 |
module Miscellaneous.A259439 (a259439) where
import HelperSequences.A143482 (a143482)
a259439 :: Integral a => a -> a
a259439 n = a143482 n `div` n
| peterokagey/haskellOEIS | src/Miscellaneous/A259439.hs | Haskell | apache-2.0 | 149 |
{-# LANGUAGE TemplateHaskell, NoMonomorphismRestriction, FlexibleContexts,
RankNTypes #-}
{-| The WConfd functions for direct configuration manipulation
This module contains the client functions exported by WConfD for
specific configuration manipulation.
-}
{-
Copyright (C) 2014 Google Inc.
All rights reserved.
Redistribution and use in source and binary forms, with or without
modification, are permitted provided that the following conditions are
met:
1. Redistributions of source code must retain the above copyright notice,
this list of conditions and the following disclaimer.
2. Redistributions in binary form must reproduce the above copyright
notice, this list of conditions and the following disclaimer in the
documentation and/or other materials provided with the distribution.
THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS
IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDER OR
CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL,
EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO,
PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR
PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF
LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING
NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS
SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
-}
module Ganeti.WConfd.ConfigModifications where
import Control.Applicative ((<$>))
import Control.Lens (_2)
import Control.Lens.Getter ((^.))
import Control.Lens.Setter (Setter, (.~), (%~), (+~), over)
import Control.Lens.Traversal (mapMOf)
import Control.Lens.Type (Simple)
import Control.Monad (unless, when, forM_, foldM, liftM, liftM2)
import Control.Monad.Error (throwError, MonadError)
import Control.Monad.IO.Class (liftIO)
import Control.Monad.Trans.State (StateT, get, put, modify,
runStateT, execStateT)
import Data.Foldable (fold, foldMap)
import Data.List (elemIndex)
import Data.Maybe (isJust, maybeToList, fromMaybe, fromJust)
import Language.Haskell.TH (Name)
import System.Time (getClockTime, ClockTime)
import Text.Printf (printf)
import qualified Data.Map as M
import qualified Data.Set as S
import Ganeti.BasicTypes (GenericResult(..), genericResult, toError)
import Ganeti.Constants (lastDrbdPort)
import Ganeti.Errors (GanetiException(..))
import Ganeti.JSON (Container, GenericContainer(..), alterContainerL
, lookupContainer, MaybeForJSON(..), TimeAsDoubleJSON(..))
import Ganeti.Locking.Locks (ClientId, ciIdentifier)
import Ganeti.Logging.Lifted (logDebug, logInfo)
import Ganeti.Objects
import Ganeti.Objects.Lens
import Ganeti.Types (AdminState, AdminStateSource, JobId)
import Ganeti.Utils (ordNub)
import Ganeti.WConfd.ConfigState (ConfigState, csConfigData, csConfigDataL)
import Ganeti.WConfd.Monad (WConfdMonad, modifyConfigWithLock
, modifyConfigAndReturnWithLock)
import qualified Ganeti.WConfd.TempRes as T
type DiskUUID = String
type InstanceUUID = String
type NodeUUID = String
-- * accessor functions
getInstanceByUUID :: ConfigState
-> InstanceUUID
-> GenericResult GanetiException Instance
getInstanceByUUID cs uuid = lookupContainer
(Bad . ConfigurationError $
printf "Could not find instance with UUID %s" uuid)
uuid
(configInstances . csConfigData $ cs)
-- * getters
-- | Gets all logical volumes in the cluster
getAllLVs :: ConfigState -> S.Set String
getAllLVs = S.fromList . concatMap getLVsOfDisk . M.elems
. fromContainer . configDisks . csConfigData
where convert (LogicalVolume lvG lvV) = lvG ++ "/" ++ lvV
getDiskLV :: Disk -> Maybe String
getDiskLV disk = case diskLogicalId disk of
Just (LIDPlain lv) -> Just (convert lv)
_ -> Nothing
getLVsOfDisk :: Disk -> [String]
getLVsOfDisk disk = maybeToList (getDiskLV disk)
++ concatMap getLVsOfDisk (diskChildren disk)
-- | Gets the ids of nodes, instances, node groups,
-- networks, disks, nics, and the custer itself.
getAllIDs :: ConfigState -> S.Set String
getAllIDs cs =
let lvs = getAllLVs cs
keysFromC :: GenericContainer a b -> [a]
keysFromC = M.keys . fromContainer
valuesFromC :: GenericContainer a b -> [b]
valuesFromC = M.elems . fromContainer
instKeys = keysFromC . configInstances . csConfigData $ cs
nodeKeys = keysFromC . configNodes . csConfigData $ cs
instValues = map uuidOf . valuesFromC
. configInstances . csConfigData $ cs
nodeValues = map uuidOf . valuesFromC . configNodes . csConfigData $ cs
nodeGroupValues = map uuidOf . valuesFromC
. configNodegroups . csConfigData $ cs
networkValues = map uuidOf . valuesFromC
. configNetworks . csConfigData $ cs
disksValues = map uuidOf . valuesFromC . configDisks . csConfigData $ cs
nics = map nicUuid . concatMap instNics
. valuesFromC . configInstances . csConfigData $ cs
cluster = uuidOf . configCluster . csConfigData $ cs
in S.union lvs . S.fromList $ instKeys ++ nodeKeys ++ instValues ++ nodeValues
++ nodeGroupValues ++ networkValues ++ disksValues ++ nics ++ [cluster]
getAllMACs :: ConfigState -> S.Set String
getAllMACs = S.fromList . map nicMac . concatMap instNics . M.elems
. fromContainer . configInstances . csConfigData
-- | Checks if the two objects are equal,
-- excluding timestamps. The serial number of
-- current must be one greater than that of target.
--
-- If this is true, it implies that the update RPC
-- updated the config, but did not successfully return.
isIdentical :: (Eq a, SerialNoObjectL a, TimeStampObjectL a)
=> ClockTime
-> a
-> a
-> Bool
isIdentical now target current = (mTimeL .~ now $ current) ==
((serialL %~ (+1)) . (mTimeL .~ now) $ target)
-- | Checks if the two objects given have the same serial number
checkSerial :: SerialNoObject a => a -> a -> GenericResult GanetiException ()
checkSerial target current = if serialOf target == serialOf current
then Ok ()
else Bad . ConfigurationError $ printf
"Configuration object updated since it has been read: %d != %d"
(serialOf current) (serialOf target)
-- | Updates an object present in a container.
-- The presence of the object in the container
-- is determined by the uuid of the object.
--
-- A check that serial number of the
-- object is consistent with the serial number
-- of the object in the container is performed.
--
-- If the check passes, the object's serial number
-- is incremented, and modification time is updated,
-- and then is inserted into the container.
replaceIn :: (UuidObject a, TimeStampObjectL a, SerialNoObjectL a)
=> ClockTime
-> a
-> Container a
-> GenericResult GanetiException (Container a)
replaceIn now target = alterContainerL (uuidOf target) extract
where extract Nothing = Bad $ ConfigurationError
"Configuration object unknown"
extract (Just current) = do
checkSerial target current
return . Just . (serialL %~ (+1)) . (mTimeL .~ now) $ target
-- | Utility fuction that combines the two
-- possible actions that could be taken when
-- given a target.
--
-- If the target is identical to the current
-- value, we return the modification time of
-- the current value, and not change the config.
--
-- If not, we update the config.
updateConfigIfNecessary :: (Monad m, MonadError GanetiException m, Eq a,
UuidObject a, SerialNoObjectL a, TimeStampObjectL a)
=> ClockTime
-> a
-> (ConfigState -> Container a)
-> (ConfigState
-> m ((Int, ClockTime), ConfigState))
-> ConfigState
-> m ((Int, ClockTime), ConfigState)
updateConfigIfNecessary now target getContainer f cs = do
let container = getContainer cs
current <- lookupContainer (toError . Bad . ConfigurationError $
"Configuraton object unknown")
(uuidOf target)
container
if isIdentical now target current
then return ((serialOf current, mTimeOf current), cs)
else f cs
-- * UUID config checks
-- | Checks if the config has the given UUID
checkUUIDpresent :: UuidObject a
=> ConfigState
-> a
-> Bool
checkUUIDpresent cs a = uuidOf a `S.member` getAllIDs cs
-- | Checks if the given UUID is new (i.e., no in the config)
checkUniqueUUID :: UuidObject a
=> ConfigState
-> a
-> Bool
checkUniqueUUID cs a = not $ checkUUIDpresent cs a
-- * RPC checks
-- | Verifications done before adding an instance.
-- Currently confirms that the instance's macs are not
-- in use, and that the instance's UUID being
-- present (or not present) in the config based on
-- weather the instance is being replaced (or not).
--
-- TODO: add more verifications to this call;
-- the client should have a lock on the name of the instance.
addInstanceChecks :: Instance
-> Bool
-> ConfigState
-> GenericResult GanetiException ()
addInstanceChecks inst replace cs = do
let macsInUse = S.fromList (map nicMac (instNics inst))
`S.intersection` getAllMACs cs
unless (S.null macsInUse) . Bad . ConfigurationError $ printf
"Cannot add instance %s; MAC addresses %s already in use"
(show $ instName inst) (show macsInUse)
if replace
then do
let check = checkUUIDpresent cs inst
unless check . Bad . ConfigurationError $ printf
"Cannot add %s: UUID %s already in use"
(show $ instName inst) (instUuid inst)
else do
let check = checkUniqueUUID cs inst
unless check . Bad . ConfigurationError $ printf
"Cannot replace %s: UUID %s not present"
(show $ instName inst) (instUuid inst)
addDiskChecks :: Disk
-> Bool
-> ConfigState
-> GenericResult GanetiException ()
addDiskChecks disk replace cs =
if replace
then
unless (checkUUIDpresent cs disk) . Bad . ConfigurationError $ printf
"Cannot add %s: UUID %s already in use"
(show $ diskName disk) (diskUuid disk)
else
unless (checkUniqueUUID cs disk) . Bad . ConfigurationError $ printf
"Cannot replace %s: UUID %s not present"
(show $ diskName disk) (diskUuid disk)
attachInstanceDiskChecks :: InstanceUUID
-> DiskUUID
-> MaybeForJSON Int
-> ConfigState
-> GenericResult GanetiException ()
attachInstanceDiskChecks uuidInst uuidDisk idx' cs = do
let diskPresent = elem uuidDisk . map diskUuid . M.elems
. fromContainer . configDisks . csConfigData $ cs
unless diskPresent . Bad . ConfigurationError $ printf
"Disk %s doesn't exist" uuidDisk
inst <- getInstanceByUUID cs uuidInst
let numDisks = length $ instDisks inst
idx = fromMaybe numDisks (unMaybeForJSON idx')
when (idx < 0) . Bad . GenericError $
"Not accepting negative indices"
when (idx > numDisks) . Bad . GenericError $ printf
"Got disk index %d, but there are only %d" idx numDisks
let insts = M.elems . fromContainer . configInstances . csConfigData $ cs
forM_ insts (\inst' -> when (uuidDisk `elem` instDisks inst') . Bad
. ReservationError $ printf "Disk %s already attached to instance %s"
uuidDisk (show $ instName inst))
-- * Pure config modifications functions
attachInstanceDisk' :: InstanceUUID
-> DiskUUID
-> MaybeForJSON Int
-> ClockTime
-> ConfigState
-> ConfigState
attachInstanceDisk' iUuid dUuid idx' ct cs =
let inst = genericResult (error "impossible") id (getInstanceByUUID cs iUuid)
numDisks = length $ instDisks inst
idx = fromMaybe numDisks (unMaybeForJSON idx')
insert = instDisksL %~ (\ds -> take idx ds ++ [dUuid] ++ drop idx ds)
incr = instSerialL %~ (+ 1)
time = instMtimeL .~ ct
inst' = time . incr . insert $ inst
disks = updateIvNames idx inst' (configDisks . csConfigData $ cs)
ri = csConfigDataL . configInstancesL
. alterContainerL iUuid .~ Just inst'
rds = csConfigDataL . configDisksL .~ disks
in rds . ri $ cs
where updateIvNames :: Int -> Instance -> Container Disk -> Container Disk
updateIvNames idx inst (GenericContainer m) =
let dUuids = drop idx (instDisks inst)
upgradeIv m' (idx'', dUuid') =
M.adjust (diskIvNameL .~ "disk/" ++ show idx'') dUuid' m'
in GenericContainer $ foldl upgradeIv m (zip [idx..] dUuids)
-- * Monadic config modification functions which can return errors
detachInstanceDisk' :: MonadError GanetiException m
=> InstanceUUID
-> DiskUUID
-> ClockTime
-> ConfigState
-> m ConfigState
detachInstanceDisk' iUuid dUuid ct cs =
let resetIv :: MonadError GanetiException m
=> Int
-> [DiskUUID]
-> ConfigState
-> m ConfigState
resetIv startIdx disks = mapMOf (csConfigDataL . configDisksL)
(\cd -> foldM (\c (idx, dUuid') -> mapMOf (alterContainerL dUuid')
(\md -> case md of
Nothing -> throwError . ConfigurationError $
printf "Could not find disk with UUID %s" dUuid'
Just disk -> return
. Just
. (diskIvNameL .~ ("disk/" ++ show idx))
$ disk) c)
cd (zip [startIdx..] disks))
iL = csConfigDataL . configInstancesL . alterContainerL iUuid
in case cs ^. iL of
Nothing -> throwError . ConfigurationError $
printf "Could not find instance with UUID %s" iUuid
Just ist -> case elemIndex dUuid (instDisks ist) of
Nothing -> return cs
Just idx ->
let ist' = (instDisksL %~ filter (/= dUuid))
. (instSerialL %~ (+1))
. (instMtimeL .~ ct)
$ ist
cs' = iL .~ Just ist' $ cs
dks = drop (idx + 1) (instDisks ist)
in resetIv idx dks cs'
removeInstanceDisk' :: MonadError GanetiException m
=> InstanceUUID
-> DiskUUID
-> ClockTime
-> ConfigState
-> m ConfigState
removeInstanceDisk' iUuid dUuid ct =
let f cs
| elem dUuid
. fold
. fmap instDisks
. configInstances
. csConfigData
$ cs
= throwError . ProgrammerError $
printf "Cannot remove disk %s. Disk is attached to an instance" dUuid
| elem dUuid
. foldMap (:[])
. fmap diskUuid
. configDisks
. csConfigData
$ cs
= return
. ((csConfigDataL . configDisksL . alterContainerL dUuid) .~ Nothing)
. ((csConfigDataL . configClusterL . clusterSerialL) %~ (+1))
. ((csConfigDataL . configClusterL . clusterMtimeL) .~ ct)
$ cs
| otherwise = return cs
in (f =<<) . detachInstanceDisk' iUuid dUuid ct
-- * RPCs
-- | Add a new instance to the configuration, release DRBD minors,
-- and commit temporary IPs, all while temporarily holding the config
-- lock. Return True upon success and False if the config lock was not
-- available and the client should retry.
addInstance :: Instance -> ClientId -> Bool -> WConfdMonad Bool
addInstance inst cid replace = do
ct <- liftIO getClockTime
logDebug $ "AddInstance: client " ++ show (ciIdentifier cid)
++ " adding instance " ++ uuidOf inst
++ " with name " ++ show (instName inst)
let setCtime = instCtimeL .~ ct
setMtime = instMtimeL .~ ct
addInst i = csConfigDataL . configInstancesL . alterContainerL (uuidOf i)
.~ Just i
commitRes tr = mapMOf csConfigDataL $ T.commitReservedIps cid tr
r <- modifyConfigWithLock
(\tr cs -> do
toError $ addInstanceChecks inst replace cs
commitRes tr $ addInst (setMtime . setCtime $ inst) cs)
. T.releaseDRBDMinors $ uuidOf inst
logDebug $ "AddInstance: result of config modification is " ++ show r
return $ isJust r
addInstanceDisk :: InstanceUUID
-> Disk
-> MaybeForJSON Int
-> Bool
-> WConfdMonad Bool
addInstanceDisk iUuid disk idx replace = do
logInfo $ printf "Adding disk %s to configuration" (diskUuid disk)
ct <- liftIO getClockTime
let addD = csConfigDataL . configDisksL . alterContainerL (uuidOf disk)
.~ Just disk
incrSerialNo = csConfigDataL . configSerialL %~ (+1)
r <- modifyConfigWithLock (\_ cs -> do
toError $ addDiskChecks disk replace cs
let cs' = incrSerialNo . addD $ cs
toError $ attachInstanceDiskChecks iUuid (diskUuid disk) idx cs'
return $ attachInstanceDisk' iUuid (diskUuid disk) idx ct cs')
. T.releaseDRBDMinors $ uuidOf disk
return $ isJust r
attachInstanceDisk :: InstanceUUID
-> DiskUUID
-> MaybeForJSON Int
-> WConfdMonad Bool
attachInstanceDisk iUuid dUuid idx = do
ct <- liftIO getClockTime
r <- modifyConfigWithLock (\_ cs -> do
toError $ attachInstanceDiskChecks iUuid dUuid idx cs
return $ attachInstanceDisk' iUuid dUuid idx ct cs)
(return ())
return $ isJust r
-- | Detach a disk from an instance.
detachInstanceDisk :: InstanceUUID -> DiskUUID -> WConfdMonad Bool
detachInstanceDisk iUuid dUuid = do
ct <- liftIO getClockTime
isJust <$> modifyConfigWithLock
(const $ detachInstanceDisk' iUuid dUuid ct) (return ())
-- | Detach a disk from an instance and
-- remove it from the config.
removeInstanceDisk :: InstanceUUID -> DiskUUID -> WConfdMonad Bool
removeInstanceDisk iUuid dUuid = do
ct <- liftIO getClockTime
isJust <$> modifyConfigWithLock
(const $ removeInstanceDisk' iUuid dUuid ct) (return ())
-- | Remove the instance from the configuration.
removeInstance :: InstanceUUID -> WConfdMonad Bool
removeInstance iUuid = do
ct <- liftIO getClockTime
let iL = csConfigDataL . configInstancesL . alterContainerL iUuid
pL = csConfigDataL . configClusterL . clusterTcpudpPortPoolL
sL = csConfigDataL . configClusterL . clusterSerialL
mL = csConfigDataL . configClusterL . clusterMtimeL
-- Add the instances' network port to the cluster pool
f :: Monad m => StateT ConfigState m ()
f = get >>= (maybe
(return ())
(maybe
(return ())
(modify . (pL %~) . (:))
. instNetworkPort)
. (^. iL))
-- Release all IP addresses to the pool
g :: (MonadError GanetiException m, Functor m) => StateT ConfigState m ()
g = get >>= (maybe
(return ())
(mapM_ (\nic ->
when ((isJust . nicNetwork $ nic) && (isJust . nicIp $ nic)) $ do
let network = fromJust . nicNetwork $ nic
ip <- readIp4Address (fromJust . nicIp $ nic)
get >>= mapMOf csConfigDataL (T.commitReleaseIp network ip) >>= put)
. instNics)
. (^. iL))
-- Remove the instance and update cluster serial num, and mtime
h :: Monad m => StateT ConfigState m ()
h = modify $ (iL .~ Nothing) . (sL %~ (+1)) . (mL .~ ct)
isJust <$> modifyConfigWithLock (const $ execStateT (f >> g >> h)) (return ())
-- | Allocate a port.
-- The port will be taken from the available port pool or from the
-- default port range (and in this case we increase
-- highest_used_port).
allocatePort :: WConfdMonad (MaybeForJSON Int)
allocatePort = do
maybePort <- modifyConfigAndReturnWithLock (\_ cs ->
let portPoolL = csConfigDataL . configClusterL . clusterTcpudpPortPoolL
hupL = csConfigDataL . configClusterL . clusterHighestUsedPortL
in case cs ^. portPoolL of
[] -> if cs ^. hupL >= lastDrbdPort
then throwError . ConfigurationError $ printf
"The highest used port is greater than %s. Aborting." lastDrbdPort
else return (cs ^. hupL + 1, hupL %~ (+1) $ cs)
(p:ps) -> return (p, portPoolL .~ ps $ cs))
(return ())
return . MaybeForJSON $ maybePort
-- | Adds a new port to the available port pool.
addTcpUdpPort :: Int -> WConfdMonad Bool
addTcpUdpPort port =
let pL = csConfigDataL . configClusterL . clusterTcpudpPortPoolL
f :: Monad m => ConfigState -> m ConfigState
f = mapMOf pL (return . (port:) . filter (/= port))
in isJust <$> modifyConfigWithLock (const f) (return ())
-- | Set the instances' status to a given value.
setInstanceStatus :: InstanceUUID
-> MaybeForJSON AdminState
-> MaybeForJSON Bool
-> MaybeForJSON AdminStateSource
-> WConfdMonad (MaybeForJSON Instance)
setInstanceStatus iUuid m1 m2 m3 = do
ct <- liftIO getClockTime
let modifyInstance = maybe id (instAdminStateL .~) (unMaybeForJSON m1)
. maybe id (instDisksActiveL .~) (unMaybeForJSON m2)
. maybe id (instAdminStateSourceL .~) (unMaybeForJSON m3)
reviseInstance = (instSerialL %~ (+1))
. (instMtimeL .~ ct)
g :: Instance -> Instance
g i = if modifyInstance i == i
then i
else reviseInstance . modifyInstance $ i
iL = csConfigDataL . configInstancesL . alterContainerL iUuid
f :: MonadError GanetiException m => StateT ConfigState m Instance
f = get >>= (maybe
(throwError . ConfigurationError $
printf "Could not find instance with UUID %s" iUuid)
(liftM2 (>>)
(modify . (iL .~) . Just)
return . g)
. (^. iL))
MaybeForJSON <$> modifyConfigAndReturnWithLock
(const $ runStateT f) (return ())
-- | Sets the primary node of an existing instance
setInstancePrimaryNode :: InstanceUUID -> NodeUUID -> WConfdMonad Bool
setInstancePrimaryNode iUuid nUuid = isJust <$> modifyConfigWithLock
(\_ -> mapMOf (csConfigDataL . configInstancesL . alterContainerL iUuid)
(\mi -> case mi of
Nothing -> throwError . ConfigurationError $
printf "Could not find instance with UUID %s" iUuid
Just ist -> return . Just $ (instPrimaryNodeL .~ nUuid) ist))
(return ())
-- | The configuration is updated by the provided cluster
updateCluster :: Cluster -> WConfdMonad (MaybeForJSON (Int, TimeAsDoubleJSON))
updateCluster cluster = do
ct <- liftIO getClockTime
r <- modifyConfigAndReturnWithLock (\_ cs -> do
let currentCluster = configCluster . csConfigData $ cs
if isIdentical ct cluster currentCluster
then return ((serialOf currentCluster, mTimeOf currentCluster), cs)
else do
toError $ checkSerial cluster currentCluster
let updateC = (clusterSerialL %~ (+1)) . (clusterMtimeL .~ ct)
return ((serialOf cluster + 1, ct)
, csConfigDataL . configClusterL .~ updateC cluster $ cs))
(return ())
return . MaybeForJSON $ fmap (_2 %~ TimeAsDoubleJSON) r
-- | The configuration is updated by the provided node
updateNode :: Node -> WConfdMonad (MaybeForJSON (Int, TimeAsDoubleJSON))
updateNode node = do
ct <- liftIO getClockTime
let nL = csConfigDataL . configNodesL
updateC = (clusterSerialL %~ (+1)) . (clusterMtimeL .~ ct)
r <- modifyConfigAndReturnWithLock (\_ -> updateConfigIfNecessary ct node
(^. nL) (\cs -> do
nC <- toError $ replaceIn ct node (cs ^. nL)
return ((serialOf node + 1, ct), (nL .~ nC)
. (csConfigDataL . configClusterL %~ updateC)
$ cs)))
(return ())
return . MaybeForJSON $ fmap (_2 %~ TimeAsDoubleJSON) r
-- | The configuration is updated by the provided instance
updateInstance :: Instance -> WConfdMonad (MaybeForJSON (Int, TimeAsDoubleJSON))
updateInstance inst = do
ct <- liftIO getClockTime
let iL = csConfigDataL . configInstancesL
r <- modifyConfigAndReturnWithLock (\_ -> updateConfigIfNecessary ct inst
(^. iL) (\cs -> do
iC <- toError $ replaceIn ct inst (cs ^. iL)
return ((serialOf inst + 1, ct), (iL .~ iC) cs)))
(return ())
return . MaybeForJSON $ fmap (_2 %~ TimeAsDoubleJSON) r
-- | The configuration is updated by the provided nodegroup
updateNodeGroup :: NodeGroup
-> WConfdMonad (MaybeForJSON (Int, TimeAsDoubleJSON))
updateNodeGroup ng = do
ct <- liftIO getClockTime
let ngL = csConfigDataL . configNodegroupsL
r <- modifyConfigAndReturnWithLock (\_ -> updateConfigIfNecessary ct ng
(^. ngL) (\cs -> do
ngC <- toError $ replaceIn ct ng (cs ^. ngL)
return ((serialOf ng + 1, ct), (ngL .~ ngC) cs)))
(return ())
return . MaybeForJSON $ fmap (_2 %~ TimeAsDoubleJSON) r
-- | The configuration is updated by the provided network
updateNetwork :: Network -> WConfdMonad (MaybeForJSON (Int, TimeAsDoubleJSON))
updateNetwork net = do
ct <- liftIO getClockTime
let nL = csConfigDataL . configNetworksL
r <- modifyConfigAndReturnWithLock (\_ -> updateConfigIfNecessary ct net
(^. nL) (\cs -> do
nC <- toError $ replaceIn ct net (cs ^. nL)
return ((serialOf net + 1, ct), (nL .~ nC) cs)))
(return ())
return . MaybeForJSON $ fmap (_2 %~ TimeAsDoubleJSON) r
-- | The configuration is updated by the provided disk
updateDisk :: Disk -> WConfdMonad (MaybeForJSON (Int, TimeAsDoubleJSON))
updateDisk disk = do
ct <- liftIO getClockTime
let dL = csConfigDataL . configDisksL
r <- modifyConfigAndReturnWithLock (\_ -> updateConfigIfNecessary ct disk
(^. dL) (\cs -> do
dC <- toError $ replaceIn ct disk (cs ^. dL)
return ((serialOf disk + 1, ct), (dL .~ dC) cs)))
. T.releaseDRBDMinors $ uuidOf disk
return . MaybeForJSON $ fmap (_2 %~ TimeAsDoubleJSON) r
-- | Set a particular value and bump serial in the hosting
-- structure. Arguments are a setter to focus on the part
-- of the configuration that gets serial-bumped, and a modification
-- of that part. The function will do the change and bump the serial
-- in the WConfdMonad temporarily acquiring the configuration lock.
-- Return True if that succeeded and False if the configuration lock
-- was not available; no change is done in the latter case.
changeAndBump :: (SerialNoObjectL a, TimeStampObjectL a)
=> Simple Setter ConfigState a
-> (a -> a)
-> WConfdMonad Bool
changeAndBump focus change = do
now <- liftIO getClockTime
let operation = over focus $ (serialL +~ 1) . (mTimeL .~ now) . change
liftM isJust $ modifyConfigWithLock
(\_ cs -> return . operation $ cs)
(return ())
-- | Change and bump part of the maintenance part of the configuration.
changeAndBumpMaint :: (MaintenanceData -> MaintenanceData) -> WConfdMonad Bool
changeAndBumpMaint = changeAndBump $ csConfigDataL . configMaintenanceL
-- | Set the maintenance intervall.
setMaintdRoundDelay :: Int -> WConfdMonad Bool
setMaintdRoundDelay delay = changeAndBumpMaint $ maintRoundDelayL .~ delay
-- | Clear the list of current maintenance jobs.
clearMaintdJobs :: WConfdMonad Bool
clearMaintdJobs = changeAndBumpMaint $ maintJobsL .~ []
-- | Append new jobs to the list of current maintenace jobs, if
-- not alread present.
appendMaintdJobs :: [JobId] -> WConfdMonad Bool
appendMaintdJobs jobs = changeAndBumpMaint . over maintJobsL
$ ordNub . (++ jobs)
-- | Set the autobalance flag.
setMaintdBalance :: Bool -> WConfdMonad Bool
setMaintdBalance value = changeAndBumpMaint $ maintBalanceL .~ value
-- | Set the auto-balance threshold.
setMaintdBalanceThreshold :: Double -> WConfdMonad Bool
setMaintdBalanceThreshold value = changeAndBumpMaint
$ maintBalanceThresholdL .~ value
-- | Add a name to the list of recently evacuated instances.
addMaintdEvacuated :: [String] -> WConfdMonad Bool
addMaintdEvacuated names = changeAndBumpMaint . over maintEvacuatedL
$ ordNub . (++ names)
-- | Remove a name from the list of recently evacuated instances.
rmMaintdEvacuated :: String -> WConfdMonad Bool
rmMaintdEvacuated name = changeAndBumpMaint . over maintEvacuatedL
$ filter (/= name)
-- | Update an incident to the list of known incidents; if the incident,
-- as identified by the UUID, is not present, it is added.
updateMaintdIncident :: Incident -> WConfdMonad Bool
updateMaintdIncident incident =
changeAndBumpMaint . over maintIncidentsL
$ (incident :) . filter ((/= uuidOf incident) . uuidOf)
-- | Remove an incident from the list of known incidents.
rmMaintdIncident :: String -> WConfdMonad Bool
rmMaintdIncident uuid =
changeAndBumpMaint . over maintIncidentsL
$ filter ((/= uuid) . uuidOf)
-- * The list of functions exported to RPC.
exportedFunctions :: [Name]
exportedFunctions = [ 'addInstance
, 'addInstanceDisk
, 'addTcpUdpPort
, 'allocatePort
, 'attachInstanceDisk
, 'detachInstanceDisk
, 'removeInstance
, 'removeInstanceDisk
, 'setInstancePrimaryNode
, 'setInstanceStatus
, 'updateCluster
, 'updateDisk
, 'updateInstance
, 'updateNetwork
, 'updateNode
, 'updateNodeGroup
, 'setMaintdRoundDelay
, 'clearMaintdJobs
, 'appendMaintdJobs
, 'setMaintdBalance
, 'setMaintdBalanceThreshold
, 'addMaintdEvacuated
, 'rmMaintdEvacuated
, 'updateMaintdIncident
, 'rmMaintdIncident
]
| bitemyapp/ganeti | src/Ganeti/WConfd/ConfigModifications.hs | Haskell | bsd-2-clause | 30,541 |
module Exercises181 where
import Control.Monad (join)
bind :: Monad m => (a -> m b) -> m a -> m b
bind f x = join $ fmap f x | pdmurray/haskell-book-ex | src/ch18/Exercises181.hs | Haskell | bsd-3-clause | 126 |
module Module5.Task18 where
import Data.Monoid (Sum(..))
import Control.Monad.Writer (Writer, execWriter, writer)
-- system code
type Shopping = Writer (Sum Integer) ()
shopping1 :: Shopping
shopping1 = do
purchase "Jeans" 19200
purchase "Water" 180
purchase "Lettuce" 328
-- solution code
purchase :: String -> Integer -> Shopping
purchase _ cost = writer ((), Sum cost)
total :: Shopping -> Integer
total = getSum . execWriter
| dstarcev/stepic-haskell | src/Module5/Task18.hs | Haskell | bsd-3-clause | 447 |
module Exercises.FindMissingNumbers (findMissingPair) where
findMissingPair :: [Integer] -> Maybe (Integer, Integer)
findMissingPair [] = Nothing
findMissingPair s = findMP (1, []) s
where
findMP (_, [a,b]) _ = Just (a,b)
findMP _ [] = Nothing
findMP (i, missings) (current:xs)
| i == current = findMP (nextI, missings) xs
| otherwise = if nextI == current
then findMP (succ nextI,
missings++[i]) xs
else Just (i, nextI)
where nextI = succ i
| WarKnife/exercises | src/Exercises/FindMissingNumbers.hs | Haskell | bsd-3-clause | 629 |
{-# LANGUAGE OverloadedStrings #-}
-- | Bindings to the Docker Remote API.
-- TODO Should be Network.Docker.Remote.
module Network.Docker.Remote where
import Control.Applicative ((<$>), (<*>))
import Control.Monad (mzero)
import Data.Aeson (object, FromJSON(..), ToJSON(..), Value(..), (.=), (.:), (.:?))
import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as B
import Data.Int (Int64)
import Network.Aeson.Client (apiGet)
getContainers :: GetContainers -> IO [Container]
getContainers query = do
mxs <- apiGet Nothing "unix:///var/run/docker.sock"
"/containers/json" params
case mxs of
Nothing -> error "Error in apiGet result, in getContainers."
Just xs -> return xs
where
-- Always include the size (that's what our Container data type
-- expects) -- I don't know if there is a serious performance cost
-- to always include it.
params = ("size", Just "true") : case query of
-- TODO Maybe it is possible to combine since/before/limit ?
RunningContainers -> []
AllContainers -> [("all", Just "true")]
LastContainers n -> [("limit", Just . B.pack $ show n)]
SinceContainer (ContainerId i) -> [("since", Just i)]
BeforeContainer (ContainerId i) -> [("before", Just i)]
newtype ContainerId = ContainerId ByteString
deriving Show
-- | Possible modifiers for the `getContainers` query.
data GetContainers =
RunningContainers
-- ^ Return running containers.
| AllContainers
-- ^ Return all containers, i.e. including non-running ones.
| LastContainers Int
-- ^ Return the n last containers, including non-running ones.
| SinceContainer ContainerId
-- ^ Return all containers created since the given ID, including
-- non-running ones.
| BeforeContainer ContainerId
-- ^ Return all containers created before the given ID, including
-- non-running ones.
-- | Result of `GET /containers/json`.
data Container = Container
{ containerId :: ContainerId
, containerImage :: String
, containerCommand :: String
, containerCreated :: Int64
, containerStatus :: String
-- , containerPorts :: String -- TODO
, containerSizeRw :: Int64
, containerSizeRootFs :: Int64
}
deriving Show
-- | Attempts to parse JSON into a Container.
instance FromJSON Container where
parseJSON (Object v) = Container
<$> (ContainerId <$> v .: "Id")
<*> v .: "Image"
<*> v .: "Command"
<*> v .: "Created"
<*> v .: "Status"
<*> v .: "SizeRw"
<*> v .: "SizeRootFs"
parseJSON _ = mzero
| noteed/rescoyl-checks | Network/Docker/Remote.hs | Haskell | bsd-3-clause | 2,502 |
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE OverloadedStrings #-}
module Web.ISO.Murv where
import Control.Concurrent.STM (atomically)
import Control.Concurrent.STM.TQueue (TQueue, newTQueue, readTQueue, writeTQueue)
import Control.Monad.Trans (MonadIO(..))
import Data.Text (Text)
import Data.JSString.Text (textToJSString)
import GHCJS.Foreign (jsNull)
import GHCJS.Foreign.Callback (asyncCallback1)
import GHCJS.Types (JSString(..))
import Web.ISO.Diff
import Web.ISO.Patch
import Web.ISO.Types
-- | Children [HTML action]
{-
flattenHTML :: HTML action -> HTML action
flattenHTML h@(CDATA _ _) = h
flattenHTML h@(Children _) = h
flattenHTML (Element t acts attrs children)
-}
{-
renderHTML :: forall action m. (MonadIO m) => (action -> IO ()) -> JSDocument -> HTML action -> m (Maybe JSNode)
renderHTML _ doc (CDATA _ t) = fmap (fmap toJSNode) $ createJSTextNode doc t
renderHTML handle doc (Element tag {- events -} attrs _ children) =
do me <- createJSElement doc tag
case me of
Nothing -> return Nothing
(Just e) ->
do mapM_ (\c -> appendJSChild e =<< renderHTML handle doc c) children
let events' = [ ev | Event ev <- attrs]
attrs' = [ (k,v) | Attr k v <- attrs]
liftIO $ mapM_ (\(k, v) -> setAttribute e k v) attrs'
liftIO $ mapM_ (handleEvent e) events'
return (Just $ toJSNode e)
where
handle' :: JSElement -> (Maybe JSString -> action) -> IO ()
handle' elem toAction =
do ms <- getValue elem
handle (toAction ms)
handleEvent :: JSElement -> (EventType, Maybe JSString -> action) -> IO ()
handleEvent elem (eventType, toAction) =
do cb <- asyncCallback AlwaysRetain (handle' elem toAction) -- FIXME: free ?
addEventListener elem eventType cb False
-}
{-
data MUV model action = MUV
{ model :: model
, update :: action -> model -> model
, view :: model -> HTML action
}
mainLoop :: JSDocument -> JSNode -> MUV model action -> IO ()
mainLoop document body (MUV model update view) =
do queue <- atomically newTQueue
html <- renderHTML (handleAction queue) document (view model)
removeChildren body
appendJSChild body html
loop queue model
where
handleAction queue = \action -> atomically $ writeTQueue queue action
loop queue model =
do action <- atomically $ readTQueue queue
let model' = update action model
html <- renderHTML (handleAction queue) document (view model')
removeChildren body
appendJSChild body html
loop queue model'
muv :: MUV model action -> IO ()
muv m =
do (Just document) <- currentDocument
(Just bodyList) <- getElementsByTagName document "body"
(Just body) <- item bodyList 0
mainLoop document body m
-}
data MURV model action remote = MURV
{ model :: model
, update :: action -> model -> (model, Maybe remote)
, view :: model -> (HTML action, [Canvas])
}
mainLoopRemote :: (Show action) => Text -> (Text -> action) -> JSDocument -> JSNode -> MURV model action Text -> Maybe action -> IO ()
mainLoopRemote url h document body (MURV model update view) mInitAction =
do queue <- atomically newTQueue
let (vdom, canvases) = view model
-- update HTML
html <- renderHTML (handleAction queue) document vdom
removeChildren body
appendChild body html
-- update Canvases
mapM_ drawCanvas canvases
-- xhr request
xhr <- newXMLHttpRequest
-- cb <- asyncCallback1 (\_ -> handleXHR queue xhr)
addEventListener xhr ReadyStateChange (\_ -> handleXHR queue xhr) False
-- remoteLoop queue xhr
case mInitAction of
(Just initAction) ->
handleAction queue initAction
Nothing -> return ()
loop xhr queue model vdom
where
handleXHR queue xhr =
do t <- getResponseText xhr
atomically $ writeTQueue queue (h t)
handleAction queue = \action -> atomically $ writeTQueue queue action
-- remoteLoop queue xhr = forkIO $
-- return ()
loop xhr queue model oldVDom =
do action <- atomically $ readTQueue queue
let (model', mremote') = update action model
let (vdom, canvases) = view model'
diffs = diff oldVDom (Just vdom)
-- putStrLn $ "action --> " ++ show action
-- putStrLn $ "diff --> " ++ show diffs
-- update HTML
apply (handleAction queue) document body oldVDom diffs
-- update Canvases
mapM_ drawCanvas canvases
-- html <- renderHTML (handleAction queue) document vdom
-- removeChildren body
-- appendJSChild body html
case mremote' of
Nothing -> return ()
(Just remote) ->
do open xhr "POST" url True
sendString xhr (textToJSString remote)
loop xhr queue model' vdom
murv :: (Show action) =>
Text -- ^ remote API URL
-> (Text -> action) -- ^ convert a remote response to an 'action'
-> MURV model action Text -- ^ model-update-remote-view record
-> (Maybe action) -- ^ initial action
-> IO ()
murv url h m initAction =
do (Just document) <- currentDocument
murv <- do mmurv <- getElementById document "murv"
case mmurv of
(Just murv) -> return (toJSNode murv)
Nothing ->
do (Just bodyList) <- getElementsByTagName document "body"
(Just body) <- item bodyList 0
return body
mainLoopRemote url h document murv m initAction
| stepcut/isomaniac | Web/ISO/Murv.hs | Haskell | bsd-3-clause | 5,917 |
{-# LANGUAGE BangPatterns, OverloadedStrings, ScopedTypeVariables, CPP #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# OPTIONS_GHC -fwarn-incomplete-patterns #-}
-- | Utilities for reading PBBS data files, etc.
-- TODO:
-- * It is probably a better strategy to shift the slices around to match number
-- boundaries than it is to deal with this whole fragments business. Try that.
module PBBS.FileReader
(
-- * PBBS specific
readAdjacencyGraph, parseAdjacencyGraph,
AdjacencyGraph(..), NodeID, nbrs,
-- * Generally useful utilities
readNumFile, parReadNats,
-- * Testing
t0,t1,t2,t3,t3B,t4,t5,
unitTests
) where
import Control.Monad (foldM, unless)
import Control.Monad.IO.Class (liftIO)
import Control.DeepSeq (NFData,rnf)
import Control.Exception (evaluate)
import Control.Concurrent (getNumCapabilities)
import Control.Monad.Par
import Control.Monad.Par.Unsafe (unsafeParIO)
import Data.Word
import Data.Char (isSpace)
import Data.Maybe (fromJust)
import qualified Data.Vector.Unboxed as U
import qualified Data.Vector.Unboxed.Mutable as M
import qualified Data.ByteString as S
import qualified Data.ByteString.Char8 as B
import Data.ByteString.Unsafe (unsafeTail, unsafeHead)
import Data.Time.Clock
import System.IO.Posix.MMap (unsafeMMapFile)
import Test.HUnit
import Prelude hiding (min,max,fst,last)
--------------------------------------------------------------------------------
-- PBBS specific:
data AdjacencyGraph =
AdjacencyGraph {
vertOffets :: U.Vector Word,
allEdges :: U.Vector Word
}
deriving (Read,Show,Eq,Ord)
nbrs :: AdjacencyGraph -> NodeID -> U.Vector NodeID
nbrs AdjacencyGraph{vertOffets, allEdges} nid =
let ind = vertOffets U.! (fromIntegral nid)
nxt = vertOffets U.! (fromIntegral (nid+1))
suff = U.drop (fromIntegral ind) allEdges in
if fromIntegral nid == U.length vertOffets - 1
then suff
else U.take (fromIntegral$ nxt-ind) suff
type NodeID = Word
-- | Read an PBBS AdjacencyGraph file into memory.
readAdjacencyGraph :: String -> IO AdjacencyGraph
readAdjacencyGraph path = do
bs <- fmap (B.dropWhile isSpace) $
unsafeMMapFile path
ncap <- getNumCapabilities
runParIO $ parseAdjacencyGraph (ncap * overPartition) bs
-- | Parse a PBBS AdjacencyGraph file from a ByteString, in parallel.
parseAdjacencyGraph :: Int -> B.ByteString -> Par AdjacencyGraph
parseAdjacencyGraph chunks bs =
case B.splitAt (B.length tag) bs of
(fst, rst) | fst /= tag -> error$ "readAdjacencyGraph: First word in file was not "++B.unpack tag
| otherwise -> do
ls <- parReadNats chunks rst
let vec = U.concat (sewEnds ls)
vec' = U.drop 2 vec
unless (U.length vec >= 2)$ error "readAdjacencyGraph: file ends prematurely."
let verts = fromIntegral$ vec U.! 0
edges = fromIntegral$ vec U.! 1
(v1,v2) = U.splitAt verts vec'
if U.length v1 == verts && U.length v2 == edges
then return (AdjacencyGraph v1 v2)
else error "readAdjacencyGraph: file doesn't contain as many entry as the header claims."
where
tag = "AdjacencyGraph"
--------------------------------------------------------------------------------
-- | How much should we partition a loop beyond what is necessary to have one task
-- per processor core.
overPartition :: Int
overPartition = 4
-- Overpartitioning definitely makes it faster... over 2X faster.
-- 8 doesn't gain anything over 4 however.. but it may reduce variance.
-- Hyperthreading shows some benefit!!
--------------------------------------------------------------------------------
#if 1
{-# INLINE readNumFile #-}
{-# INLINE parReadNats #-}
{-# INLINE readNatsPartial #-}
#else
{-# NOINLINE readNumFile #-}
{-# NOINLINE parReadNats #-}
{-# NOINLINE readNatsPartial #-}
#endif
-- | A simple front-end to 'parReadNats'. This @mmap@s the file as a byte string and
-- parses it in parallel. It returns a list of chunks of arbitrary size that may be
-- concattenated for a final result.
readNumFile :: forall nty . (U.Unbox nty, Integral nty, Eq nty, Show nty, Read nty) =>
FilePath -> IO [U.Vector nty]
readNumFile path = do
bs <- unsafeMMapFile path
ncpus <- getNumCapabilities
ls <- runParIO $ parReadNats (ncpus * overPartition) bs
return (sewEnds ls)
testReadNumFile :: forall nty . (U.Unbox nty, Integral nty, Eq nty, Show nty, Read nty) =>
FilePath -> IO [U.Vector nty]
testReadNumFile path = do
bs <- unsafeMMapFile path
ncpus <- getNumCapabilities
ls <- runParIO $ parReadNats (ncpus * overPartition) bs
consume ls
let ls' = sewEnds ls
putStrLn $ "Number of chunks after sewing: "++show (length ls')
putStrLn $ "Lengths: "++show (map U.length ls')++" sum "++ show(sum$ map U.length ls')
let flat = U.concat ls'
if (U.toList flat == map (read . B.unpack) (B.words bs))
then putStrLn "Sewed version matched expected!!"
else error "Did not match expected!"
return ls'
-- | Read all the decimal numbers from a Bytestring. They must be positive integers.
-- Be warned that this function is very permissive -- all non-digit characters are
-- treated as separators.
parReadNats :: forall nty f . (U.Unbox nty, Num nty, Eq nty) =>
Int -> S.ByteString -> Par [PartialNums nty]
parReadNats chunks bs = par
where
(each,left) = S.length bs `quotRem` chunks
mapper ind = do
let howmany = each + if ind==chunks-1 then left else 0
mychunk = S.take howmany $ S.drop (ind * each) bs
-- liftIO $ putStrLn$ "(monad-par/tree) Launching chunk of "++show howmany
partial <- unsafeParIO (readNatsPartial mychunk) -- TODO: move to ST.
return [partial]
reducer a b = return (a++b) -- Quadratic, but just at the chunk level.
par :: Par [PartialNums nty]
par = do _ <- new
parMapReduceRangeThresh 1 (InclusiveRange 0 (chunks - 1))
mapper reducer []
--------------------------------------------------------------------------------
-- Partially parsed number fragments
--------------------------------------------------------------------------------
-- | A sequence of parsed numbers with ragged edges.
data PartialNums n = Compound !(Maybe (RightFrag n)) ![U.Vector n] !(Maybe (LeftFrag n))
| Single !(MiddleFrag n)
deriving (Show,Eq,Ord,Read)
-- | This represents the rightmost portion of a decimal number that was interrupted
-- in the middle.
data RightFrag n = RightFrag {
numDigits :: {-# UNPACK #-} !Int,
partialParse :: !n
-- ^ The partialParse will need to be combined with the other half
-- through addition (shifting first if it represents a left-half).
}
deriving (Show,Eq,Ord,Read)
data LeftFrag n = LeftFrag !n
deriving (Show,Eq,Ord,Read)
-- | A fragment from the middle of a number, (potentially) missing pieces on both ends.
data MiddleFrag n = MiddleFrag {-# UNPACK #-} !Int !n
deriving (Show,Eq,Ord,Read)
instance NFData (RightFrag n) where
rnf (RightFrag _ _) = ()
instance NFData (LeftFrag n) where
rnf (LeftFrag _) = ()
instance NFData (MiddleFrag n) where
rnf (MiddleFrag _ _) = ()
instance NFData (PartialNums n) where
rnf (Compound a b c) = a `seq` b `seq` c `seq` ()
rnf (Single a) = rnf a
{-# INLINE sewEnds #-}
-- Sew up a list of ragged-edged fragments into a list of normal vector chunks.
sewEnds :: forall nty . (U.Unbox nty, Integral nty, Eq nty) => [PartialNums nty] -> [U.Vector nty]
sewEnds [] = []
sewEnds origls = loop Nothing origls
where
loop _mleft [] = error "Internal error."
loop mleft [last] =
case last of
Single _ -> error "sewEnds: Got a MiddleFrag at the END!"
Compound _ _ (Just _) -> error "sewEnds: Got a LeftFrag at the END!"
Compound rf ls Nothing -> sew mleft rf ls
loop mleft (Compound rf ls lf : rst) =
sew mleft rf ls ++ loop lf rst
-- TODO: Test this properly... doesn't occur in most files:
loop mleft (Single (MiddleFrag nd m) : rst) =
case mleft of
Nothing -> loop (Just (LeftFrag m)) rst
Just (LeftFrag n) -> loop (Just (LeftFrag (shiftCombine n m nd))) rst
sew mleft rf ls =
case (mleft, rf) of
(Just (LeftFrag n), Just (RightFrag nd m)) -> let num = shiftCombine n m nd in
U.singleton num : ls
(Just (LeftFrag n), Nothing) -> U.singleton n : ls
(Nothing, Just (RightFrag _ m)) -> U.singleton m : ls
(Nothing, Nothing) -> ls
shiftCombine n m nd = n * (10 ^ (fromIntegral nd :: nty)) + m
--------------------------------------------------------------------------------
-- Efficient sequential parsing
--------------------------------------------------------------------------------
-- {-# SPECIALIZE readNatsPartial :: S.ByteString -> IO [PartialNums Word] #-}
-- {-# SPECIALIZE readNatsPartial :: S.ByteString -> IO [PartialNums Word8] #-}
-- {-# SPECIALIZE readNatsPartial :: S.ByteString -> IO [PartialNums Word16] #-}
-- {-# SPECIALIZE readNatsPartial :: S.ByteString -> IO [PartialNums Word32] #-}
-- {-# SPECIALIZE readNatsPartial :: S.ByteString -> IO [PartialNums Word64] #-}
-- {-# SPECIALIZE readNatsPartial :: S.ByteString -> IO [PartialNums Int] #-}
-- | Sequentially reads all the unsigned decimal (ASCII) numbers within a a
-- bytestring, which is typically a slice of a larger bytestring. Extra complexity
-- is needed to deal with the cases where numbers are cut off at the boundaries.
-- readNatsPartial :: S.ByteString -> IO [PartialNums Word]
readNatsPartial :: forall nty . (U.Unbox nty, Num nty, Eq nty) => S.ByteString -> IO (PartialNums nty)
readNatsPartial bs
| bs == S.empty = return (Single (MiddleFrag 0 0))
| otherwise = do
let hd = S.head bs
charsTotal = S.length bs
initV <- M.new (vecSize charsTotal)
(vs,lfrg) <- scanfwd charsTotal 0 initV [] hd (S.tail bs)
-- putStrLn$ " Got back "++show(length vs)++" partial reads"
-- Once we are done looping we need some logic to figure out the corner cases:
----------------------------------------
let total = sum $ map U.length vs
if digit hd then
(let first = U.head $ head vs -- The first (possibly partial) number parsed.
rest = U.tail (head vs) : tail vs
-- If we start in the middle of a number, then the RightFrag goes till the first whitespace:
rfrag = Just (RightFrag (fromJust$ S.findIndex (not . digit) bs) first) in
if total == 0
then case lfrg of
Nothing -> return (Compound rfrag [] Nothing)
Just (LeftFrag w) -> return (Single$ MiddleFrag charsTotal w)
else return (Compound rfrag rest lfrg)) -- Rfrag gobbles first.
else return (Compound Nothing vs lfrg) -- May be completely empty (whitespace only).
----------------------------------------
where
-- Given the number of characters left, how big of a vector chunk shall we allocate?
-- vecSize n = min chunkSize ((n `quot` 2) + 1) -- At minimum numbers must be one character.
vecSize n = ((n `quot` 4) + 1) -- Assume at least 3 digit numbers... tunable parameter.
-- loop :: Int -> Int -> nty -> M.IOVector nty -> Word8 -> S.ByteString ->
-- IO (M.IOVector nty, Maybe (LeftFrag nty), Int)
loop !lmt !ind !acc !vec !vecacc !nxt !rst
-- Extend the currently accumulating number in 'acc':
| digit nxt =
let acc' = (10*acc + (fromIntegral nxt-48)) in
if lmt == 1
then closeOff vec vecacc ind (Just (LeftFrag acc'))
else loop (lmt-1) ind acc' vec vecacc (unsafeHead rst) (unsafeTail rst)
-- When we fill one chunk we move to the next:
| ind >= M.length vec = do
-- putStrLn$ " [!] Overflow at "++show ind++", next chunk!"
-- putStr$ show ind ++ " "
fresh <- M.new (vecSize$ S.length rst) :: IO (M.IOVector nty)
vec' <- U.unsafeFreeze vec
loop lmt 0 acc fresh (vec':vecacc) nxt rst
| otherwise =
do M.write vec ind acc
if lmt == 1
then closeOff vec vecacc (ind+1) Nothing
else scanfwd (lmt-1) (ind+1) vec vecacc (unsafeHead rst) (unsafeTail rst)
scanfwd !lmt !ind !vec !vecacc !nxt !rst
| digit nxt = loop lmt ind 0 vec vecacc nxt rst -- We've started a number.
| otherwise = if lmt == 1
then closeOff vec vecacc ind Nothing
else scanfwd (lmt-1) ind vec vecacc (unsafeHead rst) (unsafeTail rst)
digit nxt = nxt >= 48 && nxt <= 57
closeOff vec vecacc ind frag =
do vec' <- U.unsafeFreeze (M.take ind vec)
return (reverse (vec':vecacc), frag)
--------------------------------------------------------------------------------
-- Unit Tests
--------------------------------------------------------------------------------
unitTests :: [Test]
unitTests =
[ TestCase$ assertEqual "t1" (Compound (Just (RightFrag 3 (123::Word))) [U.fromList []] Nothing) =<<
readNatsPartial (S.take 4 "123 4")
, TestCase$ assertEqual "t1" (Compound (Just (RightFrag 3 (123::Word))) [U.fromList []] (Just (LeftFrag 4))) =<<
readNatsPartial (S.take 5 "123 4")
, TestCase$ assertEqual "t3" (Single (MiddleFrag 3 (123::Word))) =<<
readNatsPartial (S.take 3 "123")
, TestCase$ assertEqual "t4" (Single (MiddleFrag 2 (12::Word))) =<<
readNatsPartial (S.take 2 "123")
, TestCase$ assertEqual "t5" (Compound Nothing [] (Just (LeftFrag (12::Word32)))) =<<
readNatsPartial (S.take 3 " 123")
, TestCase$ assertEqual "t6"
(Compound (Just (RightFrag 3 23)) [U.fromList [456]] (Just (LeftFrag (78::Word64)))) =<<
readNatsPartial (S.take 10 "023 456 789")
]
---------------------------
-- Bigger, temporary tests:
---------------------------
t0 :: IO [U.Vector Word]
-- t0 = testReadNumFile "/tmp/grid_1000"
-- t0 = testReadNumFile "../../pbbs/breadthFirstSearch/graphData/data/3Dgrid_J_1000"
t0 = testReadNumFile "1000_nums"
t1 :: IO [U.Vector Word]
-- t1 = testReadNumFile "/tmp/grid_125000"
t1 = testReadNumFile "../../pbbs/breadthFirstSearch/graphData/data/3Dgrid_J_125000"
t2 :: IO ()
t2 = do t0_ <- getCurrentTime
ls <- readNumFile "../../pbbs/breadthFirstSearch/graphData/data/3Dgrid_J_10000000"
t1_ <- getCurrentTime
let v :: U.Vector Word
v = U.concat ls
putStrLn$ "Resulting vector has length: "++show (U.length v)
t2_ <- getCurrentTime
putStrLn$ "Time parsing/reading "++show (diffUTCTime t1_ t0_)++
" and coalescing "++show(diffUTCTime t2_ t1_)
-- This one is fast... but WHY? It should be the same as the hacked 1-chunk parallel versions.
t3 :: IO [PartialNums Word]
t3 = do bs <- unsafeMMapFile "../../pbbs/breadthFirstSearch/graphData/data/3Dgrid_J_10000000"
pn <- readNatsPartial bs
consume [pn]
return [pn]
-- | Try it with readFile...
t3B :: IO [PartialNums Word]
t3B = do putStrLn "Sequential version + readFile"
t0_ <- getCurrentTime
bs <- S.readFile "../../pbbs/breadthFirstSearch/graphData/data/3Dgrid_J_10000000"
t1_ <- getCurrentTime
putStrLn$ "Time to read file sequentially: "++show (diffUTCTime t1_ t0_)
pn <- readNatsPartial bs
consume [pn]
return [pn]
t4 :: IO [PartialNums Word]
t4 = do putStrLn$ "Using parReadNats + readFile"
t0_ <- getCurrentTime
bs <- S.readFile "../../pbbs/breadthFirstSearch/graphData/data/3Dgrid_J_10000000"
t1_ <- getCurrentTime
putStrLn$ "Time to read file sequentially: "++show (diffUTCTime t1_ t0_)
pns <- runParIO $ parReadNats 4 bs
consume pns
return pns
t5 :: IO ()
t5 = do t0_ <- getCurrentTime
AdjacencyGraph v1 v2 <- readAdjacencyGraph "../../pbbs/breadthFirstSearch/graphData/data/3Dgrid_J_10000000"
t1_ <- getCurrentTime
putStrLn$ "Read adjacency graph in: "++show (diffUTCTime t1_ t0_)
putStrLn$ " Edges and Verts: "++show (U.length v1, U.length v2)
return ()
-- Make sure everything is forced
consume :: (Show n, M.Unbox n) => [PartialNums n] -> IO ()
consume ox = do
evaluate (rnf ox)
putStrLn$ "Result: "++show (length ox)++" segments of output"
mapM_ fn ox
where
fn (Single (MiddleFrag c x)) = putStrLn$ " <middle frag "++ show (c,x)++">"
fn (Compound r uvs l) = putStrLn$ " <segment, lengths "++show (map U.length uvs)++", ends "++show(r,l)++">"
| adk9/pbbs-haskell | PBBS/FileReader.hs | Haskell | bsd-3-clause | 16,918 |
{-# LANGUAGE OverloadedStrings #-}
module Buildsome.Print
( posText ) where
import Data.String (IsString(..))
import Text.Parsec (SourcePos)
posText :: (Monoid s, IsString s) => SourcePos -> s
posText _ = ""
| da-x/buildsome-tst | app/Buildsome/Print.hs | Haskell | bsd-3-clause | 242 |
{-# LANGUAGE PackageImports #-}
module System.Exit (module M) where
import "base" System.Exit as M
| silkapp/base-noprelude | src/System/Exit.hs | Haskell | bsd-3-clause | 104 |
{-# LANGUAGE PatternSynonyms #-}
--------------------------------------------------------------------------------
-- |
-- Module : Graphics.GL.NV.ShaderBufferLoad
-- Copyright : (c) Sven Panne 2019
-- License : BSD3
--
-- Maintainer : Sven Panne <[email protected]>
-- Stability : stable
-- Portability : portable
--
--------------------------------------------------------------------------------
module Graphics.GL.NV.ShaderBufferLoad (
-- * Extension Support
glGetNVShaderBufferLoad,
gl_NV_shader_buffer_load,
-- * Enums
pattern GL_BUFFER_GPU_ADDRESS_NV,
pattern GL_GPU_ADDRESS_NV,
pattern GL_MAX_SHADER_BUFFER_ADDRESS_NV,
-- * Functions
glGetBufferParameterui64vNV,
glGetIntegerui64vNV,
glGetNamedBufferParameterui64vNV,
glGetUniformui64vNV,
glIsBufferResidentNV,
glIsNamedBufferResidentNV,
glMakeBufferNonResidentNV,
glMakeBufferResidentNV,
glMakeNamedBufferNonResidentNV,
glMakeNamedBufferResidentNV,
glProgramUniformui64NV,
glProgramUniformui64vNV,
glUniformui64NV,
glUniformui64vNV
) where
import Graphics.GL.ExtensionPredicates
import Graphics.GL.Tokens
import Graphics.GL.Functions
| haskell-opengl/OpenGLRaw | src/Graphics/GL/NV/ShaderBufferLoad.hs | Haskell | bsd-3-clause | 1,160 |
-- Copyright (c) 2016-present, Facebook, Inc.
-- All rights reserved.
--
-- This source code is licensed under the BSD-style license found in the
-- LICENSE file in the root directory of this source tree.
{-# LANGUAGE GADTs #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NoRebindableSyntax #-}
module Duckling.Numeral.Rules
( rules
) where
import Prelude
import Duckling.Dimensions.Types
import Duckling.Numeral.Helpers
import Duckling.Regex.Types
import Duckling.Types
ruleIntegerNumeric :: Rule
ruleIntegerNumeric = Rule
{ name = "integer (numeric)"
, pattern =
[ regex "(\\d{1,18})"
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
toInteger <$> parseInt match >>= integer
_ -> Nothing
}
ruleFractions :: Rule
ruleFractions = Rule
{ name = "fractional number"
, pattern =
[ regex "(\\d+)/(\\d+)"
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (numerator:denominator:_)):_) -> do
n <- parseDecimal False numerator
d <- parseDecimal False denominator
divide n d >>= notOkForAnyTime
_ -> Nothing
}
rules :: [Rule]
rules =
[ ruleIntegerNumeric
, ruleFractions
]
| facebookincubator/duckling | Duckling/Numeral/Rules.hs | Haskell | bsd-3-clause | 1,227 |
{-# LANGUAGE ScopedTypeVariables #-}
-- | This module provides convenience functions for interfacing @io-streams@
-- with @HsOpenSSL@. It is intended to be imported @qualified@, e.g.:
--
-- @
-- import qualified "OpenSSL" as SSL
-- import qualified "OpenSSL.Session" as SSL
-- import qualified "System.IO.Streams.SSL" as SSLStreams
--
-- \ example :: IO ('InputStream' 'ByteString', 'OutputStream' 'ByteString')
-- example = SSL.'SSL.withOpenSSL' $ do
-- ctx <- SSL.'SSL.context'
-- SSL.'SSL.contextSetDefaultCiphers' ctx
--
-- \ \-\- Note: the location of the system certificates is system-dependent,
-- \-\- on Linux systems this is usually \"\/etc\/ssl\/certs\". This
-- \-\- step is optional if you choose to disable certificate verification
-- \-\- (not recommended!).
-- SSL.'SSL.contextSetCADirectory' ctx \"\/etc\/ssl\/certs\"
-- SSL.'SSL.contextSetVerificationMode' ctx $
-- SSL.'SSL.VerifyPeer' True True Nothing
-- SSLStreams.'connect' ctx "foo.com" 4444
-- @
--
module System.IO.Streams.SSL
( connect
, withConnection
, sslToStreams
) where
import qualified Control.Exception as E
import Control.Monad (void)
import Data.ByteString.Char8 (ByteString)
import qualified Data.ByteString.Char8 as S
import Network.Socket (HostName, PortNumber)
import qualified Network.Socket as N
import OpenSSL.Session (SSL, SSLContext)
import qualified OpenSSL.Session as SSL
import System.IO.Streams (InputStream, OutputStream)
import qualified System.IO.Streams as Streams
------------------------------------------------------------------------------
bUFSIZ :: Int
bUFSIZ = 32752
------------------------------------------------------------------------------
-- | Given an existing HsOpenSSL 'SSL' connection, produces an 'InputStream' \/
-- 'OutputStream' pair.
sslToStreams :: SSL -- ^ SSL connection object
-> IO (InputStream ByteString, OutputStream ByteString)
sslToStreams ssl = do
is <- Streams.makeInputStream input
os <- Streams.makeOutputStream output
return $! (is, os)
where
input = do
s <- SSL.read ssl bUFSIZ
return $! if S.null s then Nothing else Just s
output Nothing = return $! ()
output (Just s) = SSL.write ssl s
------------------------------------------------------------------------------
-- | Convenience function for initiating an SSL connection to the given
-- @('HostName', 'PortNumber')@ combination.
--
-- Note that sending an end-of-file to the returned 'OutputStream' will not
-- close the underlying SSL connection; to do that, call:
--
-- @
-- SSL.'SSL.shutdown' ssl SSL.'SSL.Unidirectional'
-- maybe (return ()) 'N.close' $ SSL.'SSL.sslSocket' ssl
-- @
--
-- on the returned 'SSL' object.
connect :: SSLContext -- ^ SSL context. See the @HsOpenSSL@
-- documentation for information on creating
-- this.
-> HostName -- ^ hostname to connect to
-> PortNumber -- ^ port number to connect to
-> IO (InputStream ByteString, OutputStream ByteString, SSL)
connect ctx host port = do
-- Partial function here OK, network will throw an exception rather than
-- return the empty list here.
(addrInfo:_) <- N.getAddrInfo (Just hints) (Just host) (Just $ show port)
let family = N.addrFamily addrInfo
let socketType = N.addrSocketType addrInfo
let protocol = N.addrProtocol addrInfo
let address = N.addrAddress addrInfo
E.bracketOnError (N.socket family socketType protocol)
N.close
(\sock -> do N.connect sock address
ssl <- SSL.connection ctx sock
SSL.connect ssl
(is, os) <- sslToStreams ssl
return $! (is, os, ssl)
)
where
hints = N.defaultHints {
N.addrFlags = [N.AI_NUMERICSERV]
, N.addrSocketType = N.Stream
}
------------------------------------------------------------------------------
-- | Convenience function for initiating an SSL connection to the given
-- @('HostName', 'PortNumber')@ combination. The socket and SSL connection are
-- closed and deleted after the user handler runs.
--
-- /Since: 1.2.0.0./
withConnection ::
SSLContext -- ^ SSL context. See the @HsOpenSSL@
-- documentation for information on creating
-- this.
-> HostName -- ^ hostname to connect to
-> PortNumber -- ^ port number to connect to
-> (InputStream ByteString -> OutputStream ByteString -> SSL -> IO a)
-- ^ Action to run with the new connection
-> IO a
withConnection ctx host port action = do
(addrInfo:_) <- N.getAddrInfo (Just hints) (Just host) (Just $ show port)
E.bracket (connectTo addrInfo) cleanup go
where
go (is, os, ssl, _) = action is os ssl
connectTo addrInfo = do
let family = N.addrFamily addrInfo
let socketType = N.addrSocketType addrInfo
let protocol = N.addrProtocol addrInfo
let address = N.addrAddress addrInfo
E.bracketOnError (N.socket family socketType protocol)
N.close
(\sock -> do N.connect sock address
ssl <- SSL.connection ctx sock
SSL.connect ssl
(is, os) <- sslToStreams ssl
return $! (is, os, ssl, sock))
cleanup (_, os, ssl, sock) = E.mask_ $ do
eatException $! Streams.write Nothing os
eatException $! SSL.shutdown ssl $! SSL.Unidirectional
eatException $! N.close sock
hints = N.defaultHints {
N.addrFlags = [N.AI_NUMERICSERV]
, N.addrSocketType = N.Stream
}
eatException m = void m `E.catch` (\(_::E.SomeException) -> return $! ())
| snapframework/openssl-streams | src/System/IO/Streams/SSL.hs | Haskell | bsd-3-clause | 6,187 |
module Snap.Snaplet.Environments
( module Data.Configurator
, lookupConfig
, lookupConfigDefault
, lookupEnv
, lookupEnvDefault
, module Snap.Snaplet.Environments.Instances )
where
import Control.Monad.Reader
import Data.Maybe (fromMaybe)
import Data.Configurator
import Data.Configurator.Types
import qualified Data.HashMap.Lazy as HM
import Data.List (find)
import qualified Data.Text as T
import Snap.Snaplet
import Snap.Snaplet.Environments.Instances
import System.Environment (getArgs)
import Text.Regex.TDFA
-----------------------------------------------------------
--
lookupConfig :: (MonadIO (m b v), MonadSnaplet m, Configured a) => Name -> m b v (Maybe a)
lookupConfig name = do
config <- getSnapletUserConfig
liftIO $ Data.Configurator.lookup config name
lookupConfigDefault :: (MonadIO (m b v), MonadSnaplet m, Configured a)
=> Name -- ^ Key
-> a -- ^ default value
-> m b v a
lookupConfigDefault name def = liftM (fromMaybe def) (lookupConfig name)
-----------------------------------------------------------
-- Look up value under environments sub group.
-- | Look up a given name without default value.
--
lookupEnv :: (Configured a, Monad (m b v), MonadSnaplet m, MonadIO (m b v)) => Name -> m b v (Maybe a)
lookupEnv name = do
mainConf <- getSnapletUserConfig
subName <- getNameForCurEnv name mainConf
liftIO $ Data.Configurator.lookup mainConf subName
-- | This function takes current env subconfig and at its base
-- looks up given name
--
lookupEnvDefault :: (Configured a, Monad (m b v), MonadSnaplet m, MonadIO (m b v)) => Name -> a -> m b v a
lookupEnvDefault name def = liftM (fromMaybe def) (lookupEnv name)
-----------------------------------------------------------
getNameForCurEnv :: (Monad (m b v), MonadSnaplet m, MonadIO (m b v)) => Name -> Config -> m b v Name
getNameForCurEnv name cfg = do
env <- getCurrentEnv cfg
return $ T.pack $ "app.environments." ++ env ++ "." ++ (T.unpack name)
getCurrentEnv :: (Monad (m b v), MonadSnaplet m, MonadIO (m b v)) => Config -> m b v String
getCurrentEnv cfg = do
mopt <- return . find (\a -> take 1 a == "@") =<< liftIO getArgs
case mopt of
Nothing -> do
hm <- liftIO $ getMap cfg
case filter (\k -> (T.unpack k) =~ ("app.environments." :: String)) $ HM.keys hm of
[] -> error "You have to put at least one env definition in your config file."
(x:_) -> return $ T.unpack $ (T.split (== '.') x) !! 2
Just opt -> do
hm <- liftIO $ getMap cfg
case length (filter (\k -> (T.unpack k) =~ ("app.environments." ++ (tail opt))) $ HM.keys hm) > 0 of
True -> return $ tail opt
False -> error $ "Given env name: " ++ opt ++ " wasn't found in your config file."
| kamilc/Snaplet-Environments | src/Snap/Snaplet/Environments.hs | Haskell | bsd-3-clause | 3,002 |
{-
- Claq (c) 2013 NEC Laboratories America, Inc. All rights reserved.
-
- This file is part of Claq.
- Claq is distributed under the 3-clause BSD license.
- See the LICENSE file for more details.
-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module Compile (prepareExprCoherent, prepareExprNoncoherent) where
import Data.Functor ((<$>))
import Data.Sequence (Seq)
import qualified Data.Sequence as Seq
import Data.Traversable (traverse)
import Control.Monad.Quantum.Class
import Data.Quantum.Wire
import Data.ClassicalCircuit
import qualified Data.DAG as DAG
import Data.ExitF
prepareExprGraph :: MonadQuantum Wire m => ClaCircuit (Bit Wire) -> m (Seq (Bit Wire))
prepareExprGraph (ClaCircuit g) =
DAG.foldMapDAGM (exitF return prepareNode) g
where
prepareNode (GConst c) = return $ BitConst c
prepareNode (GNot b1) = return $ negateBit b1
prepareNode (GAnd (BitConst False) _) = return $ BitConst False
prepareNode (GAnd (BitConst True) b2) = return b2
prepareNode (GAnd _ (BitConst False)) = return $ BitConst False
prepareNode (GAnd b1 (BitConst True)) = return b1
prepareNode (GAnd b1@(BitWire inv1 w1) b2@(BitWire inv2 w2))
| w1 == w2 && inv1 == inv2 =
return b1
| w1 == w2 && inv1 /= inv2 =
return $ BitConst False
| otherwise = do
w <- ancilla
destructiveToffoli w b1 b2
return $ bit w
prepareNode (GOr b1 b2) = negateBit <$> prepareNode (GAnd (negateBit b1) (negateBit b2))
prepareNode (GXor (BitConst False) b2) = return b2
prepareNode (GXor (BitConst True) b2) = return $ negateBit b2
prepareNode (GXor b1 (BitConst False)) = return b1
prepareNode (GXor b1 (BitConst True)) = return $ negateBit b1
prepareNode (GXor b1@(BitWire inv1 w1) b2@(BitWire inv2 w2))
| w1 == w2 =
return $ BitConst $ inv1 /= inv2
| otherwise = do
w <- ancilla
control b1 $ applyX w
control b2 $ applyX w
return $ bit w
prepareExprCoherent :: MonadQuantum Wire m => ClaCircuit (Bit Wire) -> Seq Int -> m (Seq Wire)
prepareExprCoherent g vs =
with (prepareExprGraph g) $ \ws ->
traverse (prepareCopy ws) vs
prepareExprNoncoherent :: MonadQuantum Wire m => ClaCircuit (Bit Wire) -> Seq Int -> m (Seq Wire)
prepareExprNoncoherent g vs = do
ws <- prepareExprGraph g
traverse (prepareCopy ws) vs
prepareCopy :: MonadQuantum w m => Seq (Bit w) -> Int -> m w
prepareCopy ws v = do
w <- ancilla
cnotWire w (Seq.index ws v)
return w
| ti1024/claq | src/Compile.hs | Haskell | bsd-3-clause | 2,573 |
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Test.Unit where
import Prelude (($), (.))
import Data.Foldable (mapM_)
import Data.Text hiding (toTitle)
import Data.Text.Titlecase
import Data.Text.Titlecase.Internal hiding (articles, conjunctions, prepositions)
import qualified Data.Text.Titlecase.Internal as Titlecase
import Test.Tasty
import Test.Tasty.HUnit
tests :: TestTree
tests = testGroup "Unit tests" [articles, conjunctions, prepositions]
articles :: TestTree
articles = testGroup "Articles" [articleFirst, articleLast, articleIgnored]
conjunctions :: TestTree
conjunctions = testGroup "Conjunctions" [conjunctionFirst, conjunctionLast, conjunctionIgnored]
prepositions :: TestTree
prepositions = testGroup "Prepositions" [prepositionFirst, prepositionLast, prepositionIgnored]
testTitlecase, testFirst, testLast, testIgnored :: Text -> Assertion
testTitlecase t = titlecase (toLower t) @?= Titlecase t
toTitleFirst :: Text -> Text
toTitleFirst t = unwords $ case words t of
[] -> []
(x:xs) -> toTitle x : xs
toTitleLast :: Text -> Text
toTitleLast t = unwords $ go $ words t
where
go [] = []
go [x] = [toTitle x]
go (x:xs) = x : go xs
testFirst t = testTitlecase $ toTitleFirst t <#> "Is First, so It Is Capitalized"
testLast t = testTitlecase $ "This Sentence Capitalizes" <#> toTitleLast t
testIgnored t = testTitlecase $ "This Sentence Keeps" <#> t <#> "As Is"
articleFirst, articleLast, articleIgnored :: TestTree
articleFirst = testCase "article is first" $ mapM_ (testFirst . unArticle) Titlecase.articles
articleLast = testCase "article is last" $ mapM_ (testLast . unArticle) Titlecase.articles
articleIgnored = testCase "article is ignored" $ mapM_ (testIgnored . unArticle) Titlecase.articles
conjunctionFirst, conjunctionLast, conjunctionIgnored :: TestTree
conjunctionFirst = testCase "conjunction is first" $ mapM_ (testFirst . unConjunction) Titlecase.conjunctions
conjunctionLast = testCase "conjunction is last" $ mapM_ (testLast . unConjunction) Titlecase.conjunctions
conjunctionIgnored = testCase "conjunction is ignored" $ mapM_ (testIgnored . unConjunction) Titlecase.conjunctions
prepositionFirst, prepositionLast, prepositionIgnored :: TestTree
prepositionFirst = testCase "preposition is first" $ mapM_ (testFirst . unPreposition) Titlecase.prepositions
prepositionLast = testCase "preposition is last" $ mapM_ (testLast . unPreposition) Titlecase.prepositions
prepositionIgnored = testCase "preposition is ignored" $ mapM_ (testIgnored . unPreposition) Titlecase.prepositions
| nkaretnikov/titlecase | tests/Test/Unit.hs | Haskell | bsd-3-clause | 2,760 |
{-# LANGUAGE TemplateHaskell #-}
module NotCPP.Utils where
import Control.Applicative ((<$>))
import Language.Haskell.TH
-- | Turns 'Nothing' into an expression representing 'Nothing', and
-- @'Just' x@ into an expression representing 'Just' applied to the
-- expression in @x@.
liftMaybe :: Maybe Exp -> Exp
liftMaybe = maybe (ConE 'Nothing) (AppE (ConE 'Just))
-- | A useful variant of 'reify' that returns 'Nothing' instead of
-- halting compilation when an error occurs (e.g. because the given
-- name was not in scope).
maybeReify :: Name -> Q (Maybe Info)
maybeReify = recoverMaybe . reify
-- | Turns a possibly-failing 'Q' action into one returning a 'Maybe'
-- value.
recoverMaybe :: Q a -> Q (Maybe a)
recoverMaybe q = recover (return Nothing) (Just <$> q)
-- | Returns @'Just' ('VarE' n)@ if the info relates to a value called
-- @n@, or 'Nothing' if it relates to a different sort of thing.
infoToExp :: Info -> Maybe Exp
infoToExp (VarI n _ _ _) = Just (VarE n)
infoToExp (DataConI n _ _ _) = Just (ConE n)
infoToExp _ = Nothing
| bmillwood/notcpp | NotCPP/Utils.hs | Haskell | bsd-3-clause | 1,046 |
import Data.STM.LinkedList (LinkedList)
import qualified Data.STM.LinkedList as LinkedList
import Control.Concurrent
import Control.Concurrent.STM
import Control.Exception
import Control.Monad (forM_, forever)
import Foreign.Marshal.Error (void)
type Event = String
type EventHandler = (Event -> IO ())
withEventHandler :: LinkedList EventHandler
-> EventHandler
-> IO a
-> IO a
withEventHandler list handler action =
bracket (atomically $ LinkedList.append handler list)
(atomically . LinkedList.delete)
(\_ -> action)
dispatchEvent :: LinkedList EventHandler
-> Event
-> IO ()
dispatchEvent list event = do
handlers <- atomically $ LinkedList.toList list
forM_ handlers $ \handler -> handler event
main :: IO ()
main = do
list <- LinkedList.emptyIO
let testThread listeningFor = void $ forkIO $ do
eventReceived <- atomically $ newTVar False
let handler ev = do
putStrLn $ listeningFor ++ ": Received " ++ ev
if ev == listeningFor
then atomically $ writeTVar eventReceived True
else return ()
withEventHandler list handler $ do
atomically $ do
r <- readTVar eventReceived
if r
then return ()
else retry
putStrLn $ listeningFor ++ ": Caught my event; leaving now"
testThread "brown"
testThread "chicken"
testThread "brown"
testThread "cow"
forever $ do
line <- getLine
dispatchEvent list line
| joeyadams/haskell-stm-linkedlist | testing/event-handler.hs | Haskell | bsd-3-clause | 1,705 |
module Lucid.Foundation.Typography
( module Lucid.Foundation.Typography.Types
, module Lucid.Foundation.Typography.InlineList
, module Lucid.Foundation.Typography.Labels
) where
import Lucid.Foundation.Typography.Types
import Lucid.Foundation.Typography.InlineList
import Lucid.Foundation.Typography.Labels
| athanclark/lucid-foundation | src/Lucid/Foundation/Typography.hs | Haskell | bsd-3-clause | 316 |
module Database.Hitcask(
get
, put
, delete
, Hitcask()
, connect
, connectWith
, close
, compact
, listKeys
, standardSettings
) where
import Control.Concurrent.STM
import System.IO
import System.Directory
import Database.Hitcask.Types
import Database.Hitcask.Restore
import Database.Hitcask.Get
import Database.Hitcask.Put
import Database.Hitcask.Delete
import Database.Hitcask.Compact
import Database.Hitcask.Logs
import Database.Hitcask.ListKeys
import qualified Data.HashMap.Strict as M
standardSettings :: HitcaskSettings
standardSettings = HitcaskSettings (2 * 1073741824)
connect :: FilePath -> IO Hitcask
connect dir = connectWith dir standardSettings
connectWith :: FilePath -> HitcaskSettings -> IO Hitcask
connectWith dir options = do
createDirectoryIfMissing True dir
m <- restoreFromLogDir dir
ls <- openLogFiles dir
h@(LogFile _ p) <- getOrCreateCurrent dir ls
let allLogs = if M.null ls then M.fromList [(p, h)] else ls
t <- newTVarIO $! m
l <- newTVarIO $! HitcaskLogs h allLogs
return $! Hitcask t l dir options
getOrCreateCurrent :: FilePath -> M.HashMap FilePath LogFile -> IO LogFile
getOrCreateCurrent dir ls
| M.null ls = createNewLog dir
| otherwise = return $! head (M.elems ls)
close :: Hitcask -> IO ()
close h = do
ls <- readTVarIO $ logs h
mapM_ (hClose . handle) $ M.elems (files ls)
| tcrayford/hitcask | Database/Hitcask.hs | Haskell | bsd-3-clause | 1,366 |
module Internal.BitOps
(
fixedXOR
, repeatingKeyXOR
, hamming
) where
import qualified Data.ByteString as BS
import Data.Bits
import Internal.Uncons
import Data.Monoid
import Data.Word
import Debug.Trace
fixedXOR :: BS.ByteString -> BS.ByteString -> Maybe BS.ByteString
fixedXOR bs1 bs2
| BS.length bs1 /= BS.length bs2 = Nothing
| otherwise = Just . BS.pack $ BS.zipWith xor bs1 bs2
repeatingKeyXOR :: BS.ByteString -> BS.ByteString -> BS.ByteString
repeatingKeyXOR k bs =
let repeatingKey = cycle $ BS.unpack k
unpackedBS = BS.unpack bs
in
BS.pack $ zipWith xor repeatingKey unpackedBS
hamming :: BS.ByteString -> BS.ByteString -> Int
hamming bs1 bs2 =
sum $ zipWith ((.) popCount . xor) (BS.unpack bs1) (BS.unpack bs2)
| caneroj1/Crypto-hs | src/Internal/BitOps.hs | Haskell | bsd-3-clause | 775 |
{-# LANGUAGE OverloadedStrings #-}
module Network.YAML.Snap (handleApi, handleApiPost) where
import qualified Data.ByteString as B
import qualified Data.Text.Encoding as TE
import Network.YAML
import qualified Data.Aeson as Json
import Snap
errorMsg :: Int -> B.ByteString -> Snap ()
errorMsg status msg = do
modifyResponse $ setResponseStatus status msg
writeBS msg
finishWith =<< getResponse
-- | Snap handler for POST method
handleApiPost :: Dispatcher IO -> Snap ()
handleApiPost dispatcher = method POST $ handleApi dispatcher
-- | Snap handler for any method
handleApi :: Dispatcher IO -> Snap ()
handleApi dispatcher = do
maybeMethod <- getParam "method"
case maybeMethod of
Nothing -> errorMsg 400 "No method name specified"
Just methodName -> case dispatcher (TE.decodeUtf8 methodName) of
Nothing -> errorMsg 404 "No such method"
Just method -> do
body <- readRequestBody 16384
case Json.decode body of
Nothing -> errorMsg 400 "Invalid JSON in request"
Just json -> do
result <- liftIO $ method json
writeLBS $ Json.encode result
| portnov/yaml-rpc | yaml-rpc-snap/Network/YAML/Snap.hs | Haskell | bsd-3-clause | 1,280 |
Subsets and Splits
No community queries yet
The top public SQL queries from the community will appear here once available.